summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorTakenobu Tani <takenobu.hs@gmail.com>2020-06-06 12:07:42 +0900
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-06-25 03:54:44 -0400
commitc7dd6da7e066872a949be7c914cc700182307cd2 (patch)
treeceae3a095d12be2c44e6e9794277d3e3a5329fc9
parent90f438724dbc1ef9e4b371034d44170738fe3224 (diff)
downloadhaskell-c7dd6da7e066872a949be7c914cc700182307cd2.tar.gz
Clean up haddock hyperlinks of GHC.* (part1)
This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top
-rw-r--r--compiler/GHC.hs4
-rw-r--r--compiler/GHC/Builtin/Types.hs4
-rw-r--r--compiler/GHC/Builtin/Types/Prim.hs6
-rw-r--r--compiler/GHC/Builtin/Utils.hs2
-rw-r--r--compiler/GHC/Cmm/CLabel.hs2
-rw-r--r--compiler/GHC/Cmm/Dataflow/Block.hs2
-rw-r--r--compiler/GHC/Cmm/Info.hs2
-rw-r--r--compiler/GHC/Core.hs24
-rw-r--r--compiler/GHC/Core/Class.hs2
-rw-r--r--compiler/GHC/Core/Coercion.hs6
-rw-r--r--compiler/GHC/Core/DataCon.hs6
-rw-r--r--compiler/GHC/Core/FVs.hs4
-rw-r--r--compiler/GHC/Core/InstEnv.hs6
-rw-r--r--compiler/GHC/Core/Lint.hs2
-rw-r--r--compiler/GHC/Core/Make.hs8
-rw-r--r--compiler/GHC/Core/Map.hs2
-rw-r--r--compiler/GHC/Core/Opt/OccurAnal.hs2
-rw-r--r--compiler/GHC/Core/Rules.hs2
-rw-r--r--compiler/GHC/Core/SimpleOpt.hs2
-rw-r--r--compiler/GHC/Core/Subst.hs12
-rw-r--r--compiler/GHC/Core/TyCo/FVs.hs18
-rw-r--r--compiler/GHC/Core/TyCo/Ppr.hs2
-rw-r--r--compiler/GHC/Core/TyCo/Rep.hs10
-rw-r--r--compiler/GHC/Core/TyCon.hs18
-rw-r--r--compiler/GHC/Core/Type.hs16
-rw-r--r--compiler/GHC/Core/Utils.hs4
-rw-r--r--compiler/GHC/Data/FastString.hs6
-rw-r--r--compiler/GHC/Data/FastString/Env.hs2
-rw-r--r--compiler/GHC/Driver/Main.hs10
-rw-r--r--compiler/GHC/Driver/Make.hs2
-rw-r--r--compiler/GHC/Driver/Plugins.hs4
-rw-r--r--compiler/GHC/Driver/Session.hs18
-rw-r--r--compiler/GHC/Driver/Types.hs12
-rw-r--r--compiler/GHC/Hs.hs20
-rw-r--r--compiler/GHC/Hs/Binds.hs86
-rw-r--r--compiler/GHC/Hs/Decls.hs168
-rw-r--r--compiler/GHC/Hs/Expr.hs204
-rw-r--r--compiler/GHC/Hs/ImpExp.hs46
-rw-r--r--compiler/GHC/Hs/Lit.hs2
-rw-r--r--compiler/GHC/Hs/Pat.hs40
-rw-r--r--compiler/GHC/Hs/Type.hs94
-rw-r--r--compiler/GHC/Hs/Utils.hs2
-rw-r--r--compiler/GHC/Parser/Annotation.hs12
-rw-r--r--compiler/GHC/Stg/CSE.hs4
-rw-r--r--compiler/GHC/Stg/Lift/Monad.hs10
-rw-r--r--compiler/GHC/Stg/Unarise.hs2
-rw-r--r--compiler/GHC/Types/Annotations.hs2
-rw-r--r--compiler/GHC/Types/Basic.hs12
-rw-r--r--compiler/GHC/Types/CostCentre/State.hs2
-rw-r--r--compiler/GHC/Types/Cpr.hs6
-rw-r--r--compiler/GHC/Types/ForeignCall.hs8
-rw-r--r--compiler/GHC/Types/Id.hs30
-rw-r--r--compiler/GHC/Types/Id/Info.hs4
-rw-r--r--compiler/GHC/Types/Literal.hs2
-rw-r--r--compiler/GHC/Types/Name.hs19
-rw-r--r--compiler/GHC/Types/Name/Env.hs2
-rw-r--r--compiler/GHC/Types/Name/Occurrence.hs12
-rw-r--r--compiler/GHC/Types/Name/Reader.hs32
-rw-r--r--compiler/GHC/Types/RepType.hs4
-rw-r--r--compiler/GHC/Types/SrcLoc.hs2
-rw-r--r--compiler/GHC/Types/Unique.hs4
-rw-r--r--compiler/GHC/Types/Unique/DSet.hs2
-rw-r--r--compiler/GHC/Types/Unique/FM.hs6
-rw-r--r--compiler/GHC/Types/Var.hs16
-rw-r--r--compiler/GHC/Types/Var/Set.hs2
65 files changed, 542 insertions, 537 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs
index a3fff116a0..4cb2977155 100644
--- a/compiler/GHC.hs
+++ b/compiler/GHC.hs
@@ -1010,7 +1010,7 @@ desugarModule tcm = do
--
-- A module must be loaded before dependent modules can be typechecked. This
-- always includes generating a 'ModIface' and, depending on the
--- 'DynFlags.hscTarget', may also include code generation.
+-- @DynFlags@\'s 'GHC.Driver.Session.hscTarget', may also include code generation.
--
-- This function will always cause recompilation and will always overwrite
-- previous compilation results (potentially files on disk).
@@ -1145,7 +1145,7 @@ compileCore simplify fn = do
getModuleGraph :: GhcMonad m => m ModuleGraph -- ToDo: DiGraph ModSummary
getModuleGraph = liftM hsc_mod_graph getSession
--- | Return @True@ <==> module is loaded.
+-- | Return @True@ \<==> module is loaded.
isLoaded :: GhcMonad m => ModuleName -> m Bool
isLoaded m = withSession $ \hsc_env ->
return $! isJust (lookupHpt (hsc_HPT hsc_env) m)
diff --git a/compiler/GHC/Builtin/Types.hs b/compiler/GHC/Builtin/Types.hs
index d568851727..e5fbbcc9a3 100644
--- a/compiler/GHC/Builtin/Types.hs
+++ b/compiler/GHC/Builtin/Types.hs
@@ -10,7 +10,7 @@ Wired-in knowledge about {\em non-primitive} types
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
-- | This module is about types that can be defined in Haskell, but which
--- must be wired into the compiler nonetheless. C.f module GHC.Builtin.Types.Prim
+-- must be wired into the compiler nonetheless. C.f module "GHC.Builtin.Types.Prim"
module GHC.Builtin.Types (
-- * Helper functions defined here
mkWiredInTyConName, -- This is used in GHC.Builtin.Types.Literals to define the
@@ -1755,7 +1755,7 @@ mkTupleTy boxity tys = mkTupleTy1 boxity tys
-- | Make a tuple type. The list of types should /not/ include any
-- RuntimeRep specifications. Boxed 1-tuples are *not* flattened.
-- See Note [One-tuples] and Note [Don't flatten tuples from HsSyn]
--- in GHC.Core.Make
+-- in "GHC.Core.Make"
mkTupleTy1 :: Boxity -> [Type] -> Type
mkTupleTy1 Boxed tys = mkTyConApp (tupleTyCon Boxed (length tys)) tys
mkTupleTy1 Unboxed tys = mkTyConApp (tupleTyCon Unboxed (length tys))
diff --git a/compiler/GHC/Builtin/Types/Prim.hs b/compiler/GHC/Builtin/Types/Prim.hs
index dc366bfd60..aa4ba96c8e 100644
--- a/compiler/GHC/Builtin/Types/Prim.hs
+++ b/compiler/GHC/Builtin/Types/Prim.hs
@@ -9,7 +9,7 @@ Wired-in knowledge about primitive types
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
-- | This module defines TyCons that can't be expressed in Haskell.
--- They are all, therefore, wired-in TyCons. C.f module GHC.Builtin.Types
+-- They are all, therefore, wired-in TyCons. C.f module "GHC.Builtin.Types"
module GHC.Builtin.Types.Prim(
mkPrimTyConName, -- For implicit parameters in GHC.Builtin.Types only
@@ -138,7 +138,7 @@ import Data.Char
primTyCons :: [TyCon]
primTyCons = unexposedPrimTyCons ++ exposedPrimTyCons
--- | Primitive 'TyCon's that are defined in "GHC.Prim" but not exposed.
+-- | Primitive 'TyCon's that are defined in GHC.Prim but not exposed.
-- It's important to keep these separate as we don't want users to be able to
-- write them (see #15209) or see them in GHCi's @:browse@ output
-- (see #12023).
@@ -149,7 +149,7 @@ unexposedPrimTyCons
, eqPhantPrimTyCon
]
--- | Primitive 'TyCon's that are defined in, and exported from, "GHC.Prim".
+-- | Primitive 'TyCon's that are defined in, and exported from, GHC.Prim.
exposedPrimTyCons :: [TyCon]
exposedPrimTyCons
= [ addrPrimTyCon
diff --git a/compiler/GHC/Builtin/Utils.hs b/compiler/GHC/Builtin/Utils.hs
index 4dbbefd80c..75515de9f2 100644
--- a/compiler/GHC/Builtin/Utils.hs
+++ b/compiler/GHC/Builtin/Utils.hs
@@ -111,7 +111,7 @@ Note [About wired-in things]
-- | This list is used to ensure that when you say "Prelude.map" in your source
-- code, or in an interface file, you get a Name with the correct known key (See
--- Note [Known-key names] in GHC.Builtin.Names)
+-- Note [Known-key names] in "GHC.Builtin.Names")
knownKeyNames :: [Name]
knownKeyNames
| debugIsOn
diff --git a/compiler/GHC/Cmm/CLabel.hs b/compiler/GHC/Cmm/CLabel.hs
index cacfe7a6aa..6c9810c10e 100644
--- a/compiler/GHC/Cmm/CLabel.hs
+++ b/compiler/GHC/Cmm/CLabel.hs
@@ -164,7 +164,7 @@ import GHC.CmmToAsm.Config
- By the C-- AST to identify labels
- - By the unregisterised C code generator ("PprC") for naming functions (hence
+ - By the unregisterised C code generator (\"PprC\") for naming functions (hence
the name 'CLabel')
- By the native and LLVM code generators to identify labels
diff --git a/compiler/GHC/Cmm/Dataflow/Block.hs b/compiler/GHC/Cmm/Dataflow/Block.hs
index 1fa8d4dfd6..f3876e241c 100644
--- a/compiler/GHC/Cmm/Dataflow/Block.hs
+++ b/compiler/GHC/Cmm/Dataflow/Block.hs
@@ -46,7 +46,7 @@ import GHC.Prelude
-- | Used at the type level to indicate "open" vs "closed" structure.
data Extensibility
-- | An "open" structure with a unique, unnamed control-flow edge flowing in
- -- or out. "Fallthrough" and concatenation are permitted at an open point.
+ -- or out. \"Fallthrough\" and concatenation are permitted at an open point.
= Open
-- | A "closed" structure which supports control transfer only through the use
-- of named labels---no "fallthrough" is permitted. The number of control-flow
diff --git a/compiler/GHC/Cmm/Info.hs b/compiler/GHC/Cmm/Info.hs
index e9c3ded71c..3dcff4a517 100644
--- a/compiler/GHC/Cmm/Info.hs
+++ b/compiler/GHC/Cmm/Info.hs
@@ -281,7 +281,7 @@ mkSRTLit platform _ (Just lbl) = ([CmmLabel lbl], CmmInt 1 (halfWordWidth platfo
-- | Is the SRT offset field inline in the info table on this platform?
--
-- See the section "Referring to an SRT from the info table" in
--- Note [SRTs] in GHC.Cmm.Info.Build
+-- Note [SRTs] in "GHC.Cmm.Info.Build"
inlineSRT :: Platform -> Bool
inlineSRT platform = platformArch platform == ArchX86_64
&& platformTablesNextToCode platform
diff --git a/compiler/GHC/Core.hs b/compiler/GHC/Core.hs
index 7cc8d968b6..613aef8f95 100644
--- a/compiler/GHC/Core.hs
+++ b/compiler/GHC/Core.hs
@@ -144,10 +144,10 @@ These data types are the heart of the compiler
-- We get from Haskell source to this Core language in a number of stages:
--
-- 1. The source code is parsed into an abstract syntax tree, which is represented
--- by the data type 'GHC.Hs.Expr.HsExpr' with the names being 'RdrName.RdrNames'
+-- by the data type 'GHC.Hs.Expr.HsExpr' with the names being 'GHC.Types.Name.Reader.RdrNames'
--
--- 2. This syntax tree is /renamed/, which attaches a 'Unique.Unique' to every 'RdrName.RdrName'
--- (yielding a 'Name.Name') to disambiguate identifiers which are lexically identical.
+-- 2. This syntax tree is /renamed/, which attaches a 'GHC.Types.Unique.Unique' to every 'GHC.Types.Name.Reader.RdrName'
+-- (yielding a 'GHC.Types.Name.Name') to disambiguate identifiers which are lexically identical.
-- For example, this program:
--
-- @
@@ -164,7 +164,7 @@ These data types are the heart of the compiler
-- But see Note [Shadowing] below.
--
-- 3. The resulting syntax tree undergoes type checking (which also deals with instantiating
--- type class arguments) to yield a 'GHC.Hs.Expr.HsExpr' type that has 'Id.Id' as it's names.
+-- type class arguments) to yield a 'GHC.Hs.Expr.HsExpr' type that has 'GHC.Types.Id.Id' as it's names.
--
-- 4. Finally the syntax tree is /desugared/ from the expressive 'GHC.Hs.Expr.HsExpr' type into
-- this 'Expr' type, which has far fewer constructors and hence is easier to perform
@@ -965,10 +965,10 @@ data Tickish id =
{ breakpointId :: !Int
, breakpointFVs :: [id] -- ^ the order of this list is important:
-- it matches the order of the lists in the
- -- appropriate entry in GHC.Driver.Types.ModBreaks.
+ -- appropriate entry in 'GHC.Driver.Types.ModBreaks'.
--
-- Careful about substitution! See
- -- Note [substTickish] in GHC.Core.Subst.
+ -- Note [substTickish] in "GHC.Core.Subst".
}
-- | A source note.
@@ -1338,7 +1338,7 @@ data CoreRule
-- Rough-matching stuff
-- see comments with InstEnv.ClsInst( is_cls, is_rough )
- ru_fn :: Name, -- ^ Name of the 'Id.Id' at the head of this rule
+ ru_fn :: Name, -- ^ Name of the 'GHC.Types.Id.Id' at the head of this rule
ru_rough :: [Maybe Name], -- ^ Name at the head of each argument to the left hand side
-- Proper-matching stuff
@@ -1355,7 +1355,7 @@ data CoreRule
ru_auto :: Bool, -- ^ @True@ <=> this rule is auto-generated
-- (notably by Specialise or SpecConstr)
-- @False@ <=> generated at the user's behest
- -- See Note [Trimming auto-rules] in GHC.Iface.Tidy
+ -- See Note [Trimming auto-rules] in "GHC.Iface.Tidy"
-- for the sole purpose of this field.
ru_origin :: !Module, -- ^ 'Module' the rule was defined in, used
@@ -1429,14 +1429,14 @@ ruleActivation :: CoreRule -> Activation
ruleActivation (BuiltinRule { }) = AlwaysActive
ruleActivation (Rule { ru_act = act }) = act
--- | The 'Name' of the 'Id.Id' at the head of the rule left hand side
+-- | The 'Name' of the 'GHC.Types.Id.Id' at the head of the rule left hand side
ruleIdName :: CoreRule -> Name
ruleIdName = ru_fn
isLocalRule :: CoreRule -> Bool
isLocalRule = ru_local
--- | Set the 'Name' of the 'Id.Id' at the head of the rule left hand side
+-- | Set the 'Name' of the 'GHC.Types.Id.Id' at the head of the rule left hand side
setRuleIdName :: Name -> CoreRule -> CoreRule
setRuleIdName nm ru = ru { ru_fn = nm }
@@ -1452,13 +1452,13 @@ The @Unfolding@ type is declared here to avoid numerous loops
-- | Records the /unfolding/ of an identifier, which is approximately the form the
-- identifier would have if we substituted its definition in for the identifier.
--- This type should be treated as abstract everywhere except in GHC.Core.Unfold
+-- This type should be treated as abstract everywhere except in "GHC.Core.Unfold"
data Unfolding
= NoUnfolding -- ^ We have no information about the unfolding.
| BootUnfolding -- ^ We have no information about the unfolding, because
-- this 'Id' came from an @hi-boot@ file.
- -- See Note [Inlining and hs-boot files] in GHC.CoreToIface
+ -- See Note [Inlining and hs-boot files] in "GHC.CoreToIface"
-- for what this is used for.
| OtherCon [AltCon] -- ^ It ain't one of these constructors.
diff --git a/compiler/GHC/Core/Class.hs b/compiler/GHC/Core/Class.hs
index 2c2f8c353b..25df472486 100644
--- a/compiler/GHC/Core/Class.hs
+++ b/compiler/GHC/Core/Class.hs
@@ -77,7 +77,7 @@ data Class
--
-- Here fun-deps are [([a,b],[c]), ([a,c],[b])]
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow'',
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow'',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
type FunDep a = ([a],[a])
diff --git a/compiler/GHC/Core/Coercion.hs b/compiler/GHC/Core/Coercion.hs
index e482e14811..c749ed0280 100644
--- a/compiler/GHC/Core/Coercion.hs
+++ b/compiler/GHC/Core/Coercion.hs
@@ -2445,7 +2445,7 @@ mkReprPrimEqPred ty1 ty2
-- a nominal coercion between the types. This is useful when optimizing
-- transitivity over coercion applications, where splitting two
-- AppCos might yield different kinds. See Note [EtaAppCo] in
--- GHC.Core.Coercion.Opt.
+-- "GHC.Core.Coercion.Opt".
buildCoercion :: Type -> Type -> CoercionN
buildCoercion orig_ty1 orig_ty2 = go orig_ty1 orig_ty2
where
@@ -2956,11 +2956,11 @@ bad_co_hole_co :: Coercion -> Monoid.Any
hole _ = Monoid.Any False
-- | Is there a blocking coercion hole in this type? See
--- TcCanonical Note [Equalities with incompatible kinds]
+-- "GHC.Tc.Solver.Canonical" Note [Equalities with incompatible kinds]
badCoercionHole :: Type -> Bool
badCoercionHole = Monoid.getAny . bad_co_hole_ty
-- | Is there a blocking coercion hole in this coercion? See
--- TcCanonical Note [Equalities with incompatible kinds]
+-- GHC.Tc.Solver.Canonical Note [Equalities with incompatible kinds]
badCoercionHoleCo :: Coercion -> Bool
badCoercionHoleCo = Monoid.getAny . bad_co_hole_co
diff --git a/compiler/GHC/Core/DataCon.hs b/compiler/GHC/Core/DataCon.hs
index e6f3d39690..60a7052643 100644
--- a/compiler/GHC/Core/DataCon.hs
+++ b/compiler/GHC/Core/DataCon.hs
@@ -302,8 +302,8 @@ Note that (Foo a) might not be an instance of Ord.
-- | A data constructor
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
--- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnComma'
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+-- 'GHC.Parser.Annotation.AnnClose','GHC.Parser.Annotation.AnnComma'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
data DataCon
@@ -953,7 +953,7 @@ mkDataCon :: Name
-> KnotTied ThetaType -- ^ Theta-type occurring before the arguments proper
-> [KnotTied (Scaled Type)] -- ^ Original argument types
-> KnotTied Type -- ^ Original result type
- -> RuntimeRepInfo -- ^ See comments on 'TyCon.RuntimeRepInfo'
+ -> RuntimeRepInfo -- ^ See comments on 'GHC.Core.TyCon.RuntimeRepInfo'
-> KnotTied TyCon -- ^ Representation type constructor
-> ConTag -- ^ Constructor tag
-> ThetaType -- ^ The "stupid theta", context of the data
diff --git a/compiler/GHC/Core/FVs.hs b/compiler/GHC/Core/FVs.hs
index 700f961b9a..b3fb267816 100644
--- a/compiler/GHC/Core/FVs.hs
+++ b/compiler/GHC/Core/FVs.hs
@@ -106,7 +106,7 @@ exprFreeVars :: CoreExpr -> VarSet
exprFreeVars = fvVarSet . exprFVs
-- | Find all locally-defined free Ids or type variables in an expression
--- returning a composable FV computation. See Note [FV naming conventions] in GHC.Utils.FV
+-- returning a composable FV computation. See Note [FV naming conventions] in "GHC.Utils.FV"
-- for why export it.
exprFVs :: CoreExpr -> FV
exprFVs = filterFV isLocalVar . expr_fvs
@@ -151,7 +151,7 @@ exprsFreeVars :: [CoreExpr] -> VarSet
exprsFreeVars = fvVarSet . exprsFVs
-- | Find all locally-defined free Ids or type variables in several expressions
--- returning a composable FV computation. See Note [FV naming conventions] in GHC.Utils.FV
+-- returning a composable FV computation. See Note [FV naming conventions] in "GHC.Utils.FV"
-- for why export it.
exprsFVs :: [CoreExpr] -> FV
exprsFVs exprs = mapUnionFV exprFVs exprs
diff --git a/compiler/GHC/Core/InstEnv.hs b/compiler/GHC/Core/InstEnv.hs
index de20f6f4b4..61d3ac0f55 100644
--- a/compiler/GHC/Core/InstEnv.hs
+++ b/compiler/GHC/Core/InstEnv.hs
@@ -453,7 +453,7 @@ classInstances (InstEnvs { ie_global = pkg_ie, ie_local = home_ie, ie_visible =
Nothing -> []
-- | Checks for an exact match of ClsInst in the instance environment.
--- We use this when we do signature checking in GHC.Tc.Module
+-- We use this when we do signature checking in "GHC.Tc.Module"
memberInstEnv :: InstEnv -> ClsInst -> Bool
memberInstEnv inst_env ins_item@(ClsInst { is_cls_nm = cls_nm } ) =
maybe False (\(ClsIE items) -> any (identicalDFunType ins_item) items)
@@ -835,8 +835,8 @@ lookupInstEnv :: Bool -- Check Safe Haskell overlap restrictions
-> Class -> [Type] -- What we are looking for
-> ClsInstLookupResult
-- ^ See Note [Rules for instance lookup]
--- ^ See Note [Safe Haskell Overlapping Instances] in GHC.Tc.Solver
--- ^ See Note [Safe Haskell Overlapping Instances Implementation] in GHC.Tc.Solver
+-- ^ See Note [Safe Haskell Overlapping Instances] in "GHC.Tc.Solver"
+-- ^ See Note [Safe Haskell Overlapping Instances Implementation] in "GHC.Tc.Solver"
lookupInstEnv check_overlap_safe
(InstEnvs { ie_global = pkg_ie
, ie_local = home_ie
diff --git a/compiler/GHC/Core/Lint.hs b/compiler/GHC/Core/Lint.hs
index d14bc633fe..85f490f68b 100644
--- a/compiler/GHC/Core/Lint.hs
+++ b/compiler/GHC/Core/Lint.hs
@@ -722,7 +722,7 @@ lintRhs _bndr rhs = fmap lf_check_static_ptrs getLintFlags >>= go
go _ = markAllJoinsBad $ lintCoreExpr rhs
-- | Lint the RHS of a join point with expected join arity of @n@ (see Note
--- [Join points] in GHC.Core).
+-- [Join points] in "GHC.Core").
lintJoinLams :: JoinArity -> Maybe Id -> CoreExpr -> LintM (LintedType, UsageEnv)
lintJoinLams join_arity enforce rhs
= go join_arity rhs
diff --git a/compiler/GHC/Core/Make.hs b/compiler/GHC/Core/Make.hs
index ccaa385801..e586a92e44 100644
--- a/compiler/GHC/Core/Make.hs
+++ b/compiler/GHC/Core/Make.hs
@@ -135,7 +135,7 @@ mkCoreConApps con args = mkCoreApps (Var (dataConWorkId con)) args
-- | Construct an expression which represents the application of a number of
-- expressions to another. The leftmost expression in the list is applied first
-- Respects the let/app invariant by building a case expression where necessary
--- See Note [Core let/app invariant] in GHC.Core
+-- See Note [Core let/app invariant] in "GHC.Core"
mkCoreApps :: CoreExpr -> [CoreExpr] -> CoreExpr
mkCoreApps fun args
= fst $
@@ -147,7 +147,7 @@ mkCoreApps fun args
-- | Construct an expression which represents the application of one expression
-- to the other
-- Respects the let/app invariant by building a case expression where necessary
--- See Note [Core let/app invariant] in GHC.Core
+-- See Note [Core let/app invariant] in "GHC.Core"
mkCoreApp :: SDoc -> CoreExpr -> CoreExpr -> CoreExpr
mkCoreApp s fun arg
= fst $ mkCoreAppTyped s (fun, exprType fun) arg
@@ -157,7 +157,7 @@ mkCoreApp s fun arg
-- function is not exported and used in the definition of 'mkCoreApp' and
-- 'mkCoreApps'.
-- Respects the let/app invariant by building a case expression where necessary
--- See Note [Core let/app invariant] in GHC.Core
+-- See Note [Core let/app invariant] in "GHC.Core"
mkCoreAppTyped :: SDoc -> (CoreExpr, Type) -> CoreExpr -> (CoreExpr, Type)
mkCoreAppTyped _ (fun, fun_ty) (Type ty)
= (App fun (Type ty), piResultTy fun_ty ty)
@@ -193,7 +193,7 @@ mkWildEvBinder pred = mkWildValBinder Many pred
-- that you expect to use only at a *binding* site. Do not use it at
-- occurrence sites because it has a single, fixed unique, and it's very
-- easy to get into difficulties with shadowing. That's why it is used so little.
--- See Note [WildCard binders] in GHC.Core.Opt.Simplify.Env
+-- See Note [WildCard binders] in "GHC.Core.Opt.Simplify.Env"
mkWildValBinder :: Mult -> Type -> Id
mkWildValBinder w ty = mkLocalIdOrCoVar wildCardName w ty
-- "OrCoVar" since a coercion can be a scrutinee with -fdefer-type-errors
diff --git a/compiler/GHC/Core/Map.hs b/compiler/GHC/Core/Map.hs
index f8304d0d25..bf0b56ae40 100644
--- a/compiler/GHC/Core/Map.hs
+++ b/compiler/GHC/Core/Map.hs
@@ -481,7 +481,7 @@ data TypeMapX a
-- Note that there is no tyconapp case; see Note [Equality on AppTys] in GHC.Core.Type
-- | Squeeze out any synonyms, and change TyConApps to nested AppTys. Why the
--- last one? See Note [Equality on AppTys] in GHC.Core.Type
+-- last one? See Note [Equality on AppTys] in "GHC.Core.Type"
--
-- Note, however, that we keep Constraint and Type apart here, despite the fact
-- that they are both synonyms of TYPE 'LiftedRep (see #11715).
diff --git a/compiler/GHC/Core/Opt/OccurAnal.hs b/compiler/GHC/Core/Opt/OccurAnal.hs
index 156cb3df99..9cc0953efd 100644
--- a/compiler/GHC/Core/Opt/OccurAnal.hs
+++ b/compiler/GHC/Core/Opt/OccurAnal.hs
@@ -2850,7 +2850,7 @@ setBinderOcc occ_info bndr
-- the decision about another binding 'g' might be invalidated if (say)
-- 'f' tail-calls 'g'.
--
--- See Note [Invariants on join points] in GHC.Core.
+-- See Note [Invariants on join points] in "GHC.Core".
decideJoinPointHood :: TopLevelFlag -> UsageDetails
-> [CoreBndr]
-> Bool
diff --git a/compiler/GHC/Core/Rules.hs b/compiler/GHC/Core/Rules.hs
index 80566c2851..e8be7389b2 100644
--- a/compiler/GHC/Core/Rules.hs
+++ b/compiler/GHC/Core/Rules.hs
@@ -202,7 +202,7 @@ roughTopNames :: [CoreExpr] -> [Maybe Name]
-- Such names are either:
--
-- 1. The function finally being applied to in an application chain
--- (if that name is a GlobalId: see "Var#globalvslocal"), or
+-- (if that name is a GlobalId: see "GHC.Types.Var#globalvslocal"), or
--
-- 2. The 'TyCon' if the expression is a 'Type'
--
diff --git a/compiler/GHC/Core/SimpleOpt.hs b/compiler/GHC/Core/SimpleOpt.hs
index 9901f752b1..3029737065 100644
--- a/compiler/GHC/Core/SimpleOpt.hs
+++ b/compiler/GHC/Core/SimpleOpt.hs
@@ -1060,7 +1060,7 @@ data ConCont = CC [CoreExpr] Coercion
-- [exprIsConApp_maybe on data constructors with wrappers]. Data constructor wrappers
-- are unfolded late, but we really want to trigger case-of-known-constructor as
-- early as possible. See also Note [Activation for data constructor wrappers]
--- in GHC.Types.Id.Make.
+-- in "GHC.Types.Id.Make".
--
-- We also return the incoming InScopeSet, augmented with
-- the binders from any [FloatBind] that we return
diff --git a/compiler/GHC/Core/Subst.hs b/compiler/GHC/Core/Subst.hs
index f2b25e17e5..7beb238557 100644
--- a/compiler/GHC/Core/Subst.hs
+++ b/compiler/GHC/Core/Subst.hs
@@ -80,9 +80,9 @@ import Data.List
--
-- Some invariants apply to how you use the substitution:
--
--- 1. Note [The substitution invariant] in GHC.Core.TyCo.Subst
+-- 1. Note [The substitution invariant] in "GHC.Core.TyCo.Subst"
--
--- 2. Note [Substitutions apply only once] in GHC.Core.TyCo.Subst
+-- 2. Note [Substitutions apply only once] in "GHC.Core.TyCo.Subst"
data Subst
= Subst InScopeSet -- Variables in in scope (both Ids and TyVars) /after/
-- applying the substitution
@@ -172,7 +172,7 @@ mkEmptySubst in_scope = Subst in_scope emptyVarEnv emptyVarEnv emptyVarEnv
mkSubst :: InScopeSet -> TvSubstEnv -> CvSubstEnv -> IdSubstEnv -> Subst
mkSubst in_scope tvs cvs ids = Subst in_scope ids tvs cvs
--- | Find the in-scope set: see TyCoSubst Note [The substitution invariant]
+-- | Find the in-scope set: see "GHC.Core.TyCo.Subst" Note [The substitution invariant]
substInScope :: Subst -> InScopeSet
substInScope (Subst in_scope _ _ _) = in_scope
@@ -199,7 +199,7 @@ extendIdSubstList (Subst in_scope ids tvs cvs) prs
-- | Add a substitution for a 'TyVar' to the 'Subst'
-- The 'TyVar' *must* be a real TyVar, and not a CoVar
-- You must ensure that the in-scope set is such that
--- TyCoSubst Note [The substitution invariant] holds
+-- "GHC.Core.TyCo.Subst" Note [The substitution invariant] holds
-- after extending the substitution like this.
extendTvSubst :: Subst -> TyVar -> Type -> Subst
extendTvSubst (Subst in_scope ids tvs cvs) tv ty
@@ -215,7 +215,7 @@ extendTvSubstList subst vrs
-- | Add a substitution from a 'CoVar' to a 'Coercion' to the 'Subst':
-- you must ensure that the in-scope set satisfies
--- TyCoSubst Note [The substitution invariant]
+-- "GHC.Core.TyCo.Subst" Note [The substitution invariant]
-- after extending the substitution like this
extendCvSubst :: Subst -> CoVar -> Coercion -> Subst
extendCvSubst (Subst in_scope ids tvs cvs) v r
@@ -340,7 +340,7 @@ instance Outputable Subst where
-- | Apply a substitution to an entire 'CoreExpr'. Remember, you may only
-- apply the substitution /once/:
--- See Note [Substitutions apply only once] in GHC.Core.TyCo.Subst
+-- See Note [Substitutions apply only once] in "GHC.Core.TyCo.Subst"
--
-- Do *not* attempt to short-cut in the case of an empty substitution!
-- See Note [Extending the Subst]
diff --git a/compiler/GHC/Core/TyCo/FVs.hs b/compiler/GHC/Core/TyCo/FVs.hs
index 0d7e1cb47c..dadb82c5f5 100644
--- a/compiler/GHC/Core/TyCo/FVs.hs
+++ b/compiler/GHC/Core/TyCo/FVs.hs
@@ -523,14 +523,14 @@ closeOverKindsDSet = fvDVarSet . closeOverKindsFV . dVarSetElems
-- | `tyCoFVsOfType` that returns free variables of a type in a deterministic
-- set. For explanation of why using `VarSet` is not deterministic see
--- Note [Deterministic FV] in GHC.Utils.FV.
+-- Note [Deterministic FV] in "GHC.Utils.FV".
tyCoVarsOfTypeDSet :: Type -> DTyCoVarSet
-- See Note [Free variables of types]
tyCoVarsOfTypeDSet ty = fvDVarSet $ tyCoFVsOfType ty
-- | `tyCoFVsOfType` that returns free variables of a type in deterministic
-- order. For explanation of why using `VarSet` is not deterministic see
--- Note [Deterministic FV] in GHC.Utils.FV.
+-- Note [Deterministic FV] in "GHC.Utils.FV".
tyCoVarsOfTypeList :: Type -> [TyCoVar]
-- See Note [Free variables of types]
tyCoVarsOfTypeList ty = fvVarList $ tyCoFVsOfType ty
@@ -554,10 +554,10 @@ tyCoVarsOfTypesList tys = fvVarList $ tyCoFVsOfTypes tys
-- make the function quadratic.
-- It's exported, so that it can be composed with
-- other functions that compute free variables.
--- See Note [FV naming conventions] in GHC.Utils.FV.
+-- See Note [FV naming conventions] in "GHC.Utils.FV".
--
-- Eta-expanded because that makes it run faster (apparently)
--- See Note [FV eta expansion] in GHC.Utils.FV for explanation.
+-- See Note [FV eta expansion] in "GHC.Utils.FV" for explanation.
tyCoFVsOfType :: Type -> FV
-- See Note [Free variables of types]
tyCoFVsOfType (TyVarTy v) f bound_vars (acc_list, acc_set)
@@ -655,7 +655,7 @@ tyCoFVsOfCos (co:cos) fv_cand in_scope acc = (tyCoFVsOfCo co `unionFV` tyCoFVsOf
-- | Given a covar and a coercion, returns True if covar is almost devoid in
-- the coercion. That is, covar can only appear in Refl and GRefl.
--- See last wrinkle in Note [Unused coercion variable in ForAllCo] in GHC.Core.Coercion
+-- See last wrinkle in Note [Unused coercion variable in ForAllCo] in "GHC.Core.Coercion"
almostDevoidCoVarOfCo :: CoVar -> Coercion -> Bool
almostDevoidCoVarOfCo cv co =
almost_devoid_co_var_of_co co cv
@@ -777,7 +777,7 @@ almost_devoid_co_var_of_types (ty:tys) cv
-- See @Note [When does a tycon application need an explicit kind signature?]@.
injectiveVarsOfType :: Bool -- ^ Should we look under injective type families?
-- See Note [Coverage condition for injective type families]
- -- in GHC.Tc.Instance.Family.
+ -- in "GHC.Tc.Instance.Family".
-> Type -> FV
injectiveVarsOfType look_under_tfs = go
where
@@ -812,7 +812,7 @@ injectiveVarsOfType look_under_tfs = go
-- See @Note [When does a tycon application need an explicit kind signature?]@.
injectiveVarsOfTypes :: Bool -- ^ look under injective type families?
-- See Note [Coverage condition for injective type families]
- -- in GHC.Tc.Instance.Family.
+ -- in "GHC.Tc.Instance.Family".
-> [Type] -> FV
injectiveVarsOfTypes look_under_tfs = mapUnionFV (injectiveVarsOfType look_under_tfs)
@@ -831,7 +831,7 @@ injectiveVarsOfTypes look_under_tfs = mapUnionFV (injectiveVarsOfType look_under
-- * In the kind of a bound variable in a forall
-- * In a coercion
-- * In a Specified or Inferred argument to a function
--- See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep
+-- See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep"
invisibleVarsOfType :: Type -> FV
invisibleVarsOfType = go
where
@@ -935,7 +935,7 @@ types/kinds are fully settled and zonked.
--
-- It is also meant to be stable: that is, variables should not
-- be reordered unnecessarily. This is specified in Note [ScopedSort]
--- See also Note [Ordering of implicit variables] in GHC.Rename.HsType
+-- See also Note [Ordering of implicit variables] in "GHC.Rename.HsType"
scopedSort :: [TyCoVar] -> [TyCoVar]
scopedSort = go [] []
diff --git a/compiler/GHC/Core/TyCo/Ppr.hs b/compiler/GHC/Core/TyCo/Ppr.hs
index 44899be2ac..e08afc0d95 100644
--- a/compiler/GHC/Core/TyCo/Ppr.hs
+++ b/compiler/GHC/Core/TyCo/Ppr.hs
@@ -304,7 +304,7 @@ pprTypeApp tc tys
------------------
-- | Display all kind information (with @-fprint-explicit-kinds@) when the
-- provided 'Bool' argument is 'True'.
--- See @Note [Kind arguments in error messages]@ in GHC.Tc.Errors.
+-- See @Note [Kind arguments in error messages]@ in "GHC.Tc.Errors".
pprWithExplicitKindsWhen :: Bool -> SDoc -> SDoc
pprWithExplicitKindsWhen b
= updSDocContext $ \ctx ->
diff --git a/compiler/GHC/Core/TyCo/Rep.hs b/compiler/GHC/Core/TyCo/Rep.hs
index e72284477a..98c47aa767 100644
--- a/compiler/GHC/Core/TyCo/Rep.hs
+++ b/compiler/GHC/Core/TyCo/Rep.hs
@@ -129,7 +129,7 @@ The Class and its associated TyCon have the same Name.
-- | A global typecheckable-thing, essentially anything that has a name.
-- Not to be confused with a 'TcTyThing', which is also a typecheckable
--- thing but in the *local* context. See 'GHC.Tc.Utils.Env' for how to retrieve
+-- thing but in the *local* context. See "GHC.Tc.Utils.Env" for how to retrieve
-- a 'TyThing' given a 'Name'.
data TyThing
= AnId Id
@@ -189,7 +189,7 @@ data Type
--
-- 1) Function: must /not/ be a 'TyConApp' or 'CastTy',
-- must be another 'AppTy', or 'TyVarTy'
- -- See Note [Respecting definitional equality] (EQ1) about the
+ -- See Note [Respecting definitional equality] \(EQ1) about the
-- no 'CastTy' requirement
--
-- 2) Argument type
@@ -233,7 +233,7 @@ data Type
-- INVARIANT: The cast is never reflexive
-- INVARIANT: The Type is not a CastTy (use TransCo instead)
-- INVARIANT: The Type is not a ForAllTy over a type variable
- -- See Note [Respecting definitional equality] (EQ2), (EQ3), (EQ4)
+ -- See Note [Respecting definitional equality] \(EQ2), (EQ3), (EQ4)
| CoercionTy
Coercion -- ^ Injection of a Coercion into a type
@@ -675,7 +675,7 @@ are truly unrelated.
-- | A type labeled 'KnotTied' might have knot-tied tycons in it. See
-- Note [Type checking recursive type and class declarations] in
--- GHC.Tc.TyCl
+-- "GHC.Tc.TyCl"
type KnotTied ty = ty
{- **********************************************************************
@@ -1886,7 +1886,7 @@ data TyCoFolder env a
, tcf_covar :: env -> CoVar -> a
, tcf_hole :: env -> CoercionHole -> a
-- ^ What to do with coercion holes.
- -- See Note [Coercion holes] in GHC.Core.TyCo.Rep.
+ -- See Note [Coercion holes] in "GHC.Core.TyCo.Rep".
, tcf_tycobinder :: env -> TyCoVar -> ArgFlag -> env
-- ^ The returned env is used in the extended scope
diff --git a/compiler/GHC/Core/TyCon.hs b/compiler/GHC/Core/TyCon.hs
index 20d789bd74..8f21523ad0 100644
--- a/compiler/GHC/Core/TyCon.hs
+++ b/compiler/GHC/Core/TyCon.hs
@@ -900,7 +900,7 @@ data TyCon
}
-- | These exist only during type-checking. See Note [How TcTyCons work]
- -- in GHC.Tc.TyCl
+ -- in "GHC.Tc.TyCl"
| TcTyCon {
tyConUnique :: Unique,
tyConName :: Name,
@@ -1043,7 +1043,7 @@ mkDataTyConRhs cons
-- constructor of 'PrimRep'. This data structure allows us to store this
-- information right in the 'TyCon'. The other approach would be to look
-- up things like @RuntimeRep@'s @PrimRep@ by known-key every time.
--- See also Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType
+-- See also Note [Getting from RuntimeRep to PrimRep] in "GHC.Types.RepType"
data RuntimeRepInfo
= NoRRI -- ^ an ordinary promoted data con
| RuntimeRep ([Type] -> [PrimRep])
@@ -1078,7 +1078,7 @@ data AlgTyConFlav
(Maybe TyConRepName)
-- | Type constructors representing a class dictionary.
- -- See Note [ATyCon for classes] in GHC.Core.TyCo.Rep
+ -- See Note [ATyCon for classes] in "GHC.Core.TyCo.Rep"
| ClassTyCon
Class -- INVARIANT: the classTyCon of this Class is the
-- current tycon
@@ -1334,7 +1334,7 @@ tyConRepName_maybe _ = Nothing
-- | Make a 'Name' for the 'Typeable' representation of the given wired-in type
mkPrelTyConRepName :: Name -> TyConRepName
--- See Note [Grand plan for Typeable] in 'GHC.Tc.Instance.Typeable'.
+-- See Note [Grand plan for Typeable] in "GHC.Tc.Instance.Typeable".
mkPrelTyConRepName tc_name -- Prelude tc_name is always External,
-- so nameModule will work
= mkExternalName rep_uniq rep_mod rep_occ (nameSrcSpan tc_name)
@@ -1349,7 +1349,7 @@ mkPrelTyConRepName tc_name -- Prelude tc_name is always External,
-- | The name (and defining module) for the Typeable representation (TyCon) of a
-- type constructor.
--
--- See Note [Grand plan for Typeable] in 'GHC.Tc.Instance.Typeable'.
+-- See Note [Grand plan for Typeable] in "GHC.Tc.Instance.Typeable".
tyConRepModOcc :: Module -> OccName -> (Module, OccName)
tyConRepModOcc tc_module tc_occ = (rep_module, mkTyConRepOcc tc_occ)
where
@@ -1428,7 +1428,7 @@ See Note [RuntimeRep and PrimRep] in GHC.Types.RepType.
-- | A 'PrimRep' is an abstraction of a type. It contains information that
-- the code generator needs in order to pass arguments, return results,
-- and store values of this type. See also Note [RuntimeRep and PrimRep] in
--- GHC.Types.RepType and Note [VoidRep] in GHC.Types.RepType.
+-- "GHC.Types.RepType" and Note [VoidRep] in "GHC.Types.RepType".
data PrimRep
= VoidRep
| LiftedRep
@@ -1705,7 +1705,7 @@ mkSumTyCon name binders res_kind arity tyvars cons parent
-- mutually-recursive group of tycons; it is then zonked to a proper
-- TyCon in zonkTcTyCon.
-- See also Note [Kind checking recursive type and class declarations]
--- in GHC.Tc.TyCl.
+-- in "GHC.Tc.TyCl".
mkTcTyCon :: Name
-> [TyConBinder]
-> Kind -- ^ /result/ kind only
@@ -1907,7 +1907,7 @@ isDataTyCon _ = False
-- (where X is the role passed in):
-- If (T a1 b1 c1) ~X (T a2 b2 c2), then (a1 ~X1 a2), (b1 ~X2 b2), and (c1 ~X3 c2)
-- (where X1, X2, and X3, are the roles given by tyConRolesX tc X)
--- See also Note [Decomposing equality] in GHC.Tc.Solver.Canonical
+-- See also Note [Decomposing equality] in "GHC.Tc.Solver.Canonical"
isInjectiveTyCon :: TyCon -> Role -> Bool
isInjectiveTyCon _ Phantom = False
isInjectiveTyCon (FunTyCon {}) _ = True
@@ -1928,7 +1928,7 @@ isInjectiveTyCon (TcTyCon {}) _ = True
-- | 'isGenerativeTyCon' is true of 'TyCon's for which this property holds
-- (where X is the role passed in):
-- If (T tys ~X t), then (t's head ~X T).
--- See also Note [Decomposing equality] in GHC.Tc.Solver.Canonical
+-- See also Note [Decomposing equality] in "GHC.Tc.Solver.Canonical"
isGenerativeTyCon :: TyCon -> Role -> Bool
isGenerativeTyCon (FamilyTyCon { famTcFlav = DataFamilyTyCon _ }) Nominal = True
isGenerativeTyCon (FamilyTyCon {}) _ = False
diff --git a/compiler/GHC/Core/Type.hs b/compiler/GHC/Core/Type.hs
index e853bdd2e5..3f3a728824 100644
--- a/compiler/GHC/Core/Type.hs
+++ b/compiler/GHC/Core/Type.hs
@@ -660,7 +660,7 @@ data TyCoMapper env m
, tcm_covar :: env -> CoVar -> m Coercion
, tcm_hole :: env -> CoercionHole -> m Coercion
-- ^ What to do with coercion holes.
- -- See Note [Coercion holes] in GHC.Core.TyCo.Rep.
+ -- See Note [Coercion holes] in "GHC.Core.TyCo.Rep".
, tcm_tycobinder :: env -> TyCoVar -> ArgFlag -> m (env, TyCoVar)
-- ^ The returned env is used in the extended scope
@@ -670,7 +670,7 @@ data TyCoMapper env m
-- a) To zonk TcTyCons
-- b) To turn TcTyCons into TyCons.
-- See Note [Type checking recursive type and class declarations]
- -- in GHC.Tc.TyCl
+ -- in "GHC.Tc.TyCl"
}
{-# INLINE mapTyCo #-} -- See Note [Specialising mappers]
@@ -1326,7 +1326,7 @@ repSplitTyConApp_maybe :: HasDebugCallStack => Type -> Maybe (TyCon, [Type])
-- have enough info to extract the runtime-rep arguments that
-- the funTyCon requires. This will usually be true;
-- but may be temporarily false during canonicalization:
--- see Note [FunTy and decomposing tycon applications] in GHC.Tc.Solver.Canonical
+-- see Note [FunTy and decomposing tycon applications] in "GHC.Tc.Solver.Canonical"
--
repSplitTyConApp_maybe (TyConApp tc tys) = Just (tc, tys)
repSplitTyConApp_maybe (FunTy _ w arg res)
@@ -1367,7 +1367,7 @@ splitCastTy_maybe ty
-- | Make a 'CastTy'. The Coercion must be nominal. Checks the
-- Coercion for reflexivity, dropping it if it's reflexive.
--- See Note [Respecting definitional equality] in GHC.Core.TyCo.Rep
+-- See Note [Respecting definitional equality] in "GHC.Core.TyCo.Rep"
mkCastTy :: Type -> Coercion -> Type
mkCastTy ty co | isReflexiveCo co = ty -- (EQ2) from the Note
-- NB: Do the slow check here. This is important to keep the splitXXX
@@ -1404,7 +1404,7 @@ tyConBindersTyCoBinders = map to_tyb
-- | Drop the cast on a type, if any. If there is no
-- cast, just return the original type. This is rarely what
--- you want. The CastTy data constructor (in GHC.Core.TyCo.Rep) has the
+-- you want. The CastTy data constructor (in "GHC.Core.TyCo.Rep") has the
-- invariant that another CastTy is not inside. See the
-- data constructor for a full description of this invariant.
-- Since CastTy cannot be nested, the result of discardCast
@@ -1949,7 +1949,7 @@ isFamFreeTy (CoercionTy _) = False -- Not sure about this
-- | Does this type classify a core (unlifted) Coercion?
-- At either role nominal or representational
-- (t1 ~# t2) or (t1 ~R# t2)
--- See Note [Types for coercions, predicates, and evidence] in GHC.Core.TyCo.Rep
+-- See Note [Types for coercions, predicates, and evidence] in "GHC.Core.TyCo.Rep"
isCoVarType :: Type -> Bool
-- ToDo: should we check saturation?
isCoVarType ty
@@ -2091,7 +2091,7 @@ isPrimitiveType ty = case splitTyConApp_maybe ty of
-- in its return type, since given
-- join j @a @b x y z = e1 in e2,
-- the types of e1 and e2 must be the same, and a and b are not in scope for e2.
--- (See Note [The polymorphism rule of join points] in GHC.Core.) Returns False
+-- (See Note [The polymorphism rule of join points] in "GHC.Core".) Returns False
-- also if the type simply doesn't have enough arguments.
--
-- Note that we need to know how many arguments (type *and* value) the putative
@@ -2197,7 +2197,7 @@ eqType :: Type -> Type -> Bool
-- checks whether the types are equal, ignoring casts and coercions.
-- (The kind check is a recursive call, but since all kinds have type
-- @Type@, there is no need to check the types of kinds.)
--- See also Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep.
+-- See also Note [Non-trivial definitional equality] in "GHC.Core.TyCo.Rep".
eqType t1 t2 = isEqual $ nonDetCmpType t1 t2
-- It's OK to use nonDetCmpType here and eqType is deterministic,
-- nonDetCmpType does equality deterministically
diff --git a/compiler/GHC/Core/Utils.hs b/compiler/GHC/Core/Utils.hs
index 65ded60520..0095eef0fe 100644
--- a/compiler/GHC/Core/Utils.hs
+++ b/compiler/GHC/Core/Utils.hs
@@ -1551,7 +1551,7 @@ it's applied only to dictionaries.
-- exprIsHNF implies exprOkForSpeculation
-- exprOkForSpeculation implies exprOkForSideEffects
--
--- See Note [PrimOp can_fail and has_side_effects] in GHC.Builtin.PrimOps
+-- See Note [PrimOp can_fail and has_side_effects] in "GHC.Builtin.PrimOps"
-- and Note [Transformations affected by can_fail and has_side_effects]
--
-- As an example of the considerations in this test, consider:
@@ -1958,7 +1958,7 @@ exprIsTopLevelBindable :: CoreExpr -> Type -> Bool
-- See Note [Core top-level string literals]
-- Precondition: exprType expr = ty
-- Top-level literal strings can't even be wrapped in ticks
--- see Note [Core top-level string literals] in GHC.Core
+-- see Note [Core top-level string literals] in "GHC.Core"
exprIsTopLevelBindable expr ty
= not (mightBeUnliftedType ty)
-- Note that 'expr' may be levity polymorphic here consequently we must use
diff --git a/compiler/GHC/Data/FastString.hs b/compiler/GHC/Data/FastString.hs
index a8ffaff619..1ab1cf89e1 100644
--- a/compiler/GHC/Data/FastString.hs
+++ b/compiler/GHC/Data/FastString.hs
@@ -12,9 +12,9 @@
-- ['FastString']
--
-- * A compact, hash-consed, representation of character strings.
--- * Comparison is O(1), and you can get a 'Unique.Unique' from them.
+-- * Comparison is O(1), and you can get a 'GHC.Types.Unique.Unique' from them.
-- * Generated by 'fsLit'.
--- * Turn into 'Outputable.SDoc' with 'Outputable.ftext'.
+-- * Turn into 'GHC.Utils.Outputable.SDoc' with 'GHC.Utils.Outputable.ftext'.
--
-- ['PtrString']
--
@@ -22,7 +22,7 @@
-- * Practically no operations.
-- * Outputting them is fast.
-- * Generated by 'sLit'.
--- * Turn into 'Outputable.SDoc' with 'Outputable.ptext'
+-- * Turn into 'GHC.Utils.Outputable.SDoc' with 'GHC.Utils.Outputable.ptext'
-- * Requires manual memory management.
-- Improper use may lead to memory leaks or dangling pointers.
-- * It assumes Latin-1 as the encoding, therefore it cannot represent
diff --git a/compiler/GHC/Data/FastString/Env.hs b/compiler/GHC/Data/FastString/Env.hs
index 36fab5727c..3bc4ba6bec 100644
--- a/compiler/GHC/Data/FastString/Env.hs
+++ b/compiler/GHC/Data/FastString/Env.hs
@@ -36,7 +36,7 @@ import GHC.Data.FastString
-- | A non-deterministic set of FastStrings.
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" for explanation why it's not
-- deterministic and why it matters. Use DFastStringEnv if the set eventually
-- gets converted into a list or folded over in a way where the order
-- changes the generated code.
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index 85c68bb8e6..32eb7c4b7c 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -7,7 +7,7 @@
--
-- This module implements compilation of a Haskell source. It is
-- /not/ concerned with preprocessing of source files; this is handled
--- in GHC.Driver.Pipeline
+-- in "GHC.Driver.Pipeline"
--
-- There are various entry points depending on what mode we're in:
-- "batch" mode (@--make@), "one-shot" mode (@-c@, @-S@ etc.), and
@@ -997,10 +997,10 @@ hscCheckSafeImports tcg_env = do
--
-- The code for this is quite tricky as the whole algorithm is done in a few
-- distinct phases in different parts of the code base. See
--- GHC.Rename.Names.rnImportDecl for where package trust dependencies for a
+-- 'GHC.Rename.Names.rnImportDecl' for where package trust dependencies for a
-- module are collected and unioned. Specifically see the Note [Tracking Trust
--- Transitively] in GHC.Rename.Names and the Note [Trust Own Package] in
--- GHC.Rename.Names.
+-- Transitively] in "GHC.Rename.Names" and the Note [Trust Own Package] in
+-- "GHC.Rename.Names".
checkSafeImports :: TcGblEnv -> Hsc TcGblEnv
checkSafeImports tcg_env
= do
@@ -1768,7 +1768,7 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do
return (new_tythings, new_ictxt)
-- | Load the given static-pointer table entries into the interpreter.
--- See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable.
+-- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable".
hscAddSptEntries :: HscEnv -> [SptEntry] -> IO ()
hscAddSptEntries hsc_env entries = do
let add_spt_entry :: SptEntry -> IO ()
diff --git a/compiler/GHC/Driver/Make.hs b/compiler/GHC/Driver/Make.hs
index acb2ae91a9..a9d8d1689b 100644
--- a/compiler/GHC/Driver/Make.hs
+++ b/compiler/GHC/Driver/Make.hs
@@ -274,7 +274,7 @@ data LoadHowMuch
--
-- This function implements the core of GHC's @--make@ mode. It preprocesses,
-- compiles and loads the specified modules, avoiding re-compilation wherever
--- possible. Depending on the target (see 'DynFlags.hscTarget') compiling
+-- possible. Depending on the target (see 'GHC.Driver.Session.hscTarget') compiling
-- and loading may result in files being created on disk.
--
-- Calls the 'defaultWarnErrLogger' after each compiling each module, whether
diff --git a/compiler/GHC/Driver/Plugins.hs b/compiler/GHC/Driver/Plugins.hs
index 61fb9d69fa..9cbe60a36a 100644
--- a/compiler/GHC/Driver/Plugins.hs
+++ b/compiler/GHC/Driver/Plugins.hs
@@ -104,7 +104,7 @@ data Plugin = Plugin {
, parsedResultAction :: [CommandLineOption] -> ModSummary -> HsParsedModule
-> Hsc HsParsedModule
-- ^ Modify the module when it is parsed. This is called by
- -- GHC.Driver.Main when the parsing is successful.
+ -- "GHC.Driver.Main" when the parsing is successful.
, renamedResultAction :: [CommandLineOption] -> TcGblEnv
-> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
-- ^ Modify each group after it is renamed. This is called after each
@@ -119,7 +119,7 @@ data Plugin = Plugin {
, interfaceLoadAction :: forall lcl . [CommandLineOption] -> ModIface
-> IfM lcl ModIface
-- ^ Modify an interface that have been loaded. This is called by
- -- GHC.Iface.Load when an interface is successfully loaded. Not applied to
+ -- "GHC.Iface.Load" when an interface is successfully loaded. Not applied to
-- the loading of the plugin interface. Tools that rely on information from
-- modules other than the currently compiled one should implement this
-- function.
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index f1db2436bf..52ad38dfa2 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -457,7 +457,7 @@ data DynFlags = DynFlags {
llvmConfig :: LlvmConfig,
-- ^ N.B. It's important that this field is lazy since we load the LLVM
- -- configuration lazily. See Note [LLVM Configuration] in GHC.SysTools.
+ -- configuration lazily. See Note [LLVM Configuration] in "GHC.SysTools".
verbosity :: Int, -- ^ Verbosity level: see Note [Verbosity levels]
optLevel :: Int, -- ^ Optimisation level
debugLevel :: Int, -- ^ How much debug information to produce
@@ -500,7 +500,7 @@ data DynFlags = DynFlags {
-- by the assembler code generator (0 to disable)
liberateCaseThreshold :: Maybe Int, -- ^ Threshold for LiberateCase
floatLamArgs :: Maybe Int, -- ^ Arg count for lambda floating
- -- See GHC.Core.Opt.Monad.FloatOutSwitches
+ -- See 'GHC.Core.Opt.Monad.FloatOutSwitches'
liftLamsRecArgs :: Maybe Int, -- ^ Maximum number of arguments after lambda lifting a
-- recursive function.
@@ -729,7 +729,7 @@ data DynFlags = DynFlags {
nextWrapperNum :: IORef (ModuleEnv Int),
- -- | Machine dependent flags (-m<blah> stuff)
+ -- | Machine dependent flags (-m\<blah> stuff)
sseVersion :: Maybe SseVersion,
bmiVersion :: Maybe BmiVersion,
avx :: Bool,
@@ -882,7 +882,7 @@ data LlvmTarget = LlvmTarget
, lAttributes :: [String]
}
--- | See Note [LLVM Configuration] in GHC.SysTools.
+-- | See Note [LLVM Configuration] in "GHC.SysTools".
data LlvmConfig = LlvmConfig { llvmTargets :: [(String, LlvmTarget)]
, llvmPasses :: [(Int, String)]
}
@@ -1045,13 +1045,13 @@ targetRetainsAllBindings _ = False
-- | The 'GhcMode' tells us whether we're doing multi-module
-- compilation (controlled via the "GHC" API) or one-shot
-- (single-module) compilation. This makes a difference primarily to
--- the "Finder": in one-shot mode we look for interface files for
+-- the "GHC.Driver.Finder": in one-shot mode we look for interface files for
-- imported modules, but in multi-module mode we look for source files
-- in order to check whether they need to be recompiled.
data GhcMode
= CompManager -- ^ @\-\-make@, GHCi, etc.
| OneShot -- ^ @ghc -c Foo.hs@
- | MkDepend -- ^ @ghc -M@, see "Finder" for why we need this
+ | MkDepend -- ^ @ghc -M@, see "GHC.Driver.Finder" for why we need this
deriving Eq
instance Outputable GhcMode where
@@ -1625,7 +1625,7 @@ flattenExtensionFlags ml = foldr f defaultExtensionFlags
-- | The language extensions implied by the various language variants.
-- When updating this be sure to update the flag documentation in
--- @docs/users-guide/glasgow_exts.rst@.
+-- @docs/users_guide/exts@.
languageExtensions :: Maybe Language -> [LangExt.Extension]
languageExtensions Nothing
@@ -3614,7 +3614,7 @@ fFlagsDeps = [
-- | These @-f\<blah\>@ flags have to do with the typed-hole error message or
-- the valid hole fits in that message. See Note [Valid hole fits include ...]
--- in the GHC.Tc.Errors.Hole module. These flags can all be reversed with
+-- in the "GHC.Tc.Errors.Hole" module. These flags can all be reversed with
-- @-fno-\<blah\>@
fHoleFlags :: [(Deprecation, FlagSpec GeneralFlag)]
fHoleFlags = [
@@ -3910,7 +3910,7 @@ defaultFlags settings
-- | These are the default settings for the display and sorting of valid hole
-- fits in typed-hole error messages. See Note [Valid hole fits include ...]
- -- in the GHC.Tc.Errors.Hole module.
+ -- in the "GHC.Tc.Errors.Hole" module.
validHoleFitDefaults :: [GeneralFlag]
validHoleFitDefaults
= [ Opt_ShowTypeAppOfHoleFits
diff --git a/compiler/GHC/Driver/Types.hs b/compiler/GHC/Driver/Types.hs
index e25194c240..748658c473 100644
--- a/compiler/GHC/Driver/Types.hs
+++ b/compiler/GHC/Driver/Types.hs
@@ -1452,7 +1452,7 @@ data ModGuts
-- ^ Family instances declared in this module
mg_patsyns :: ![PatSyn], -- ^ Pattern synonyms declared in this module
mg_rules :: ![CoreRule], -- ^ Before the core pipeline starts, contains
- -- See Note [Overall plumbing for rules] in GHC.Core.Rules
+ -- See Note [Overall plumbing for rules] in "GHC.Core.Rules"
mg_binds :: !CoreProgram, -- ^ Bindings for this module
mg_foreign :: !ForeignStubs, -- ^ Foreign exports declared in this module
mg_foreign_files :: ![(ForeignSrcLang, FilePath)],
@@ -1479,7 +1479,7 @@ data ModGuts
mg_trust_pkg :: Bool, -- ^ Do we need to trust our
-- own package for Safe Haskell?
-- See Note [Trust Own Package]
- -- in GHC.Rename.Names
+ -- in "GHC.Rename.Names"
mg_doc_hdr :: !(Maybe HsDocString), -- ^ Module header.
mg_decl_docs :: !DeclDocMap, -- ^ Docs on declarations.
@@ -1526,7 +1526,7 @@ data CgGuts
cg_spt_entries :: [SptEntry]
-- ^ Static pointer table entries for static forms defined in
-- the module.
- -- See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable
+ -- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable"
}
-----------------------------------
@@ -2087,9 +2087,9 @@ Examples:
-- scope, just for a start!
-- N.B. the set of TyThings returned here *must* match the set of
--- names returned by GHC.Iface.Load.ifaceDeclImplicitBndrs, in the sense that
+-- names returned by 'GHC.Iface.Load.ifaceDeclImplicitBndrs', in the sense that
-- TyThing.getOccName should define a bijection between the two lists.
--- This invariant is used in GHC.Iface.Load.loadDecl (see note [Tricky iface loop])
+-- This invariant is used in 'GHC.Iface.Load.loadDecl' (see note [Tricky iface loop])
-- The order of the list does not matter.
implicitTyThings :: TyThing -> [TyThing]
implicitTyThings (AnId _) = []
@@ -2821,7 +2821,7 @@ soExt platform
-- module.
--
-- The graph is not necessarily stored in topologically-sorted order. Use
--- 'GHC.topSortModuleGraph' and 'Digraph.flattenSCC' to achieve this.
+-- 'GHC.topSortModuleGraph' and 'GHC.Data.Graph.Directed.flattenSCC' to achieve this.
data ModuleGraph = ModuleGraph
{ mg_mss :: [ModSummary]
, mg_non_boot :: ModuleEnv ModSummary
diff --git a/compiler/GHC/Hs.hs b/compiler/GHC/Hs.hs
index 587a0cd1b2..41876b8957 100644
--- a/compiler/GHC/Hs.hs
+++ b/compiler/GHC/Hs.hs
@@ -76,8 +76,8 @@ data HsModule
-- - @Just [...]@: as you would expect...
--
--
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen'
- -- ,'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen'
+ -- ,'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
hsmodImports :: [LImportDecl GhcPs],
@@ -89,25 +89,25 @@ data HsModule
hsmodDeprecMessage :: Maybe (Located WarningTxt),
-- ^ reason\/explanation for warning/deprecation of this module
--
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen'
- -- ,'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen'
+ -- ,'GHC.Parser.Annotation.AnnClose'
--
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
hsmodHaddockModHeader :: Maybe LHsDocString
-- ^ Haddock module info and description, unparsed
--
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen'
- -- ,'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen'
+ -- ,'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
}
- -- ^ 'ApiAnnotation.AnnKeywordId's
+ -- ^ 'GHC.Parser.Annotation.AnnKeywordId's
--
- -- - 'ApiAnnotation.AnnModule','ApiAnnotation.AnnWhere'
+ -- - 'GHC.Parser.Annotation.AnnModule','GHC.Parser.Annotation.AnnWhere'
--
- -- - 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnClose' for explicit braces and semi around
+ -- - 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnClose' for explicit braces and semi around
-- hsmodImports,hsmodDecls if this style is used.
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs
index 25bcae6ce6..08eb6d80b3 100644
--- a/compiler/GHC/Hs/Binds.hs
+++ b/compiler/GHC/Hs/Binds.hs
@@ -211,12 +211,12 @@ data HsBindLR idL idR
-- 'MatchContext'. See Note [FunBind vs PatBind] for
-- details about the relationship between FunBind and PatBind.
--
- -- 'ApiAnnotation.AnnKeywordId's
+ -- 'GHC.Parser.Annotation.AnnKeywordId's
--
- -- - 'ApiAnnotation.AnnFunId', attached to each element of fun_matches
+ -- - 'GHC.Parser.Annotation.AnnFunId', attached to each element of fun_matches
--
- -- - 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere',
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+ -- - 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnWhere',
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
FunBind {
@@ -255,9 +255,9 @@ data HsBindLR idL idR
-- relationship between FunBind and PatBind.
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang',
- -- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere',
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang',
+ -- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnWhere',
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| PatBind {
@@ -291,7 +291,7 @@ data HsBindLR idL idR
abs_exports :: [ABExport idL],
-- | Evidence bindings
- -- Why a list? See GHC.Tc.TyCl.Instance
+ -- Why a list? See "GHC.Tc.TyCl.Instance"
-- Note [Typechecking plan for instance declarations]
abs_ev_binds :: [TcEvBinds],
@@ -305,10 +305,10 @@ data HsBindLR idL idR
| PatSynBind
(XPatSynBind idL idR)
(PatSynBind idL idR)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnPattern',
- -- 'ApiAnnotation.AnnLarrow','ApiAnnotation.AnnEqual',
- -- 'ApiAnnotation.AnnWhere'
- -- 'ApiAnnotation.AnnOpen' @'{'@,'ApiAnnotation.AnnClose' @'}'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnPattern',
+ -- 'GHC.Parser.Annotation.AnnLarrow','GHC.Parser.Annotation.AnnEqual',
+ -- 'GHC.Parser.Annotation.AnnWhere'
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{'@,'GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -360,10 +360,10 @@ type instance XABE (GhcPass p) = NoExtField
type instance XXABExport (GhcPass p) = NoExtCon
--- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnPattern',
--- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnLarrow'
--- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen' @'{'@,
--- 'ApiAnnotation.AnnClose' @'}'@,
+-- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnPattern',
+-- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnLarrow',
+-- 'GHC.Parser.Annotation.AnnWhere','GHC.Parser.Annotation.AnnOpen' @'{'@,
+-- 'GHC.Parser.Annotation.AnnClose' @'}'@,
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -823,7 +823,7 @@ isEmptyIPBindsTc (IPBinds ds is) = null is && isEmptyTcEvBinds ds
-- | Located Implicit Parameter Binding
type LIPBind id = Located (IPBind id)
--- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when in a
+-- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' when in a
-- list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -835,7 +835,7 @@ type LIPBind id = Located (IPBind id)
-- (Right d), where "d" is the name of the dictionary holding the
-- evidence for the implicit parameter.
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual'
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
data IPBind id
@@ -889,8 +889,8 @@ data Sig pass
-- signature that brought them into scope, in this third field to be
-- more specific.
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon',
- -- 'ApiAnnotation.AnnComma'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon',
+ -- 'GHC.Parser.Annotation.AnnComma'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
TypeSig
@@ -902,9 +902,9 @@ data Sig pass
--
-- > pattern Single :: () => (Show a) => a -> [a]
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnPattern',
- -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnForall'
- -- 'ApiAnnotation.AnnDot','ApiAnnotation.AnnDarrow'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnPattern',
+ -- 'GHC.Parser.Annotation.AnnDcolon','GHC.Parser.Annotation.AnnForall'
+ -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDarrow'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| PatSynSig (XPatSynSig pass) [Located (IdP pass)] (LHsSigType pass)
@@ -918,8 +918,8 @@ data Sig pass
-- default op :: Eq a => a -> a -- Generic default
-- No wildcards allowed here
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDefault',
- -- 'ApiAnnotation.AnnDcolon'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDefault',
+ -- 'GHC.Parser.Annotation.AnnDcolon'
| ClassOpSig (XClassOpSig pass) Bool [Located (IdP pass)] (LHsSigType pass)
-- | A type signature in generated code, notably the code
@@ -934,8 +934,8 @@ data Sig pass
-- > infixl 8 ***
--
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnInfix',
- -- 'ApiAnnotation.AnnVal'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnInfix',
+ -- 'GHC.Parser.Annotation.AnnVal'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| FixSig (XFixSig pass) (FixitySig pass)
@@ -944,11 +944,11 @@ data Sig pass
--
-- > {#- INLINE f #-}
--
- -- - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpen' @'{-\# INLINE'@ and @'['@,
- -- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnTilde',
- -- 'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{-\# INLINE'@ and @'['@,
+ -- 'GHC.Parser.Annotation.AnnClose','GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnVal','GHC.Parser.Annotation.AnnTilde',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| InlineSig (XInlineSig pass)
@@ -959,12 +959,12 @@ data Sig pass
--
-- > {-# SPECIALISE f :: Int -> Int #-}
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnOpen' @'{-\# SPECIALISE'@ and @'['@,
- -- 'ApiAnnotation.AnnTilde',
- -- 'ApiAnnotation.AnnVal',
- -- 'ApiAnnotation.AnnClose' @']'@ and @'\#-}'@,
- -- 'ApiAnnotation.AnnDcolon'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{-\# SPECIALISE'@ and @'['@,
+ -- 'GHC.Parser.Annotation.AnnTilde',
+ -- 'GHC.Parser.Annotation.AnnVal',
+ -- 'GHC.Parser.Annotation.AnnClose' @']'@ and @'\#-}'@,
+ -- 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| SpecSig (XSpecSig pass)
@@ -981,8 +981,8 @@ data Sig pass
-- (Class tys); should be a specialisation of the
-- current instance declaration
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnInstance','ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnInstance','GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| SpecInstSig (XSpecInstSig pass) SourceText (LHsSigType pass)
@@ -992,9 +992,9 @@ data Sig pass
--
-- > {-# MINIMAL a | (b, c | (d | e)) #-}
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnVbar','ApiAnnotation.AnnComma',
- -- 'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnVbar','GHC.Parser.Annotation.AnnComma',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| MinimalSig (XMinimalSig pass)
diff --git a/compiler/GHC/Hs/Decls.hs b/compiler/GHC/Hs/Decls.hs
index 4b8f4228ec..543aafc828 100644
--- a/compiler/GHC/Hs/Decls.hs
+++ b/compiler/GHC/Hs/Decls.hs
@@ -135,7 +135,7 @@ import Data.Data hiding (TyCon,Fixity, Infix)
type LHsDecl p = Located (HsDecl p)
-- ^ When in a list this may have
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi'
--
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -541,21 +541,21 @@ type LTyClDecl pass = Located (TyClDecl pass)
data TyClDecl pass
= -- | @type/data family T :: *->*@
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
- -- 'ApiAnnotation.AnnData',
- -- 'ApiAnnotation.AnnFamily','ApiAnnotation.AnnDcolon',
- -- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpenP',
- -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnCloseP',
- -- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnRarrow',
- -- 'ApiAnnotation.AnnVbar'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
+ -- 'GHC.Parser.Annotation.AnnData',
+ -- 'GHC.Parser.Annotation.AnnFamily','GHC.Parser.Annotation.AnnDcolon',
+ -- 'GHC.Parser.Annotation.AnnWhere','GHC.Parser.Annotation.AnnOpenP',
+ -- 'GHC.Parser.Annotation.AnnDcolon','GHC.Parser.Annotation.AnnCloseP',
+ -- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnRarrow',
+ -- 'GHC.Parser.Annotation.AnnVbar'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
FamDecl { tcdFExt :: XFamDecl pass, tcdFam :: FamilyDecl pass }
| -- | @type@ declaration
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
- -- 'ApiAnnotation.AnnEqual',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
+ -- 'GHC.Parser.Annotation.AnnEqual',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
SynDecl { tcdSExt :: XSynDecl pass -- ^ Post renameer, FVs
@@ -568,11 +568,11 @@ data TyClDecl pass
| -- | @data@ declaration
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnData',
- -- 'ApiAnnotation.AnnFamily',
- -- 'ApiAnnotation.AnnNewType',
- -- 'ApiAnnotation.AnnNewType','ApiAnnotation.AnnDcolon'
- -- 'ApiAnnotation.AnnWhere',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnData',
+ -- 'GHC.Parser.Annotation.AnnFamily',
+ -- 'GHC.Parser.Annotation.AnnNewType',
+ -- 'GHC.Parser.Annotation.AnnNewType','GHC.Parser.Annotation.AnnDcolon'
+ -- 'GHC.Parser.Annotation.AnnWhere',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
DataDecl { tcdDExt :: XDataDecl pass -- ^ Post renamer, CUSK flag, FVs
@@ -594,12 +594,12 @@ data TyClDecl pass
tcdATDefs :: [LTyFamDefltDecl pass], -- ^ Associated type defaults
tcdDocs :: [LDocDecl] -- ^ Haddock docs
}
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnClass',
- -- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose'
- -- - The tcdFDs will have 'ApiAnnotation.AnnVbar',
- -- 'ApiAnnotation.AnnComma'
- -- 'ApiAnnotation.AnnRarrow'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnClass',
+ -- 'GHC.Parser.Annotation.AnnWhere','GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose'
+ -- - The tcdFDs will have 'GHC.Parser.Annotation.AnnVbar',
+ -- 'GHC.Parser.Annotation.AnnComma'
+ -- 'GHC.Parser.Annotation.AnnRarrow'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XTyClDecl !(XXTyClDecl pass)
@@ -1048,21 +1048,21 @@ type LFamilyResultSig pass = Located (FamilyResultSig pass)
-- | type Family Result Signature
data FamilyResultSig pass = -- see Note [FamilyResultSig]
NoSig (XNoSig pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' :
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' :
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| KindSig (XCKindSig pass) (LHsKind pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpenP','ApiAnnotation.AnnDcolon',
- -- 'ApiAnnotation.AnnCloseP'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpenP','GHC.Parser.Annotation.AnnDcolon',
+ -- 'GHC.Parser.Annotation.AnnCloseP'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| TyVarSig (XTyVarSig pass) (LHsTyVarBndr () pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpenP','ApiAnnotation.AnnDcolon',
- -- 'ApiAnnotation.AnnCloseP', 'ApiAnnotation.AnnEqual'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpenP','GHC.Parser.Annotation.AnnDcolon',
+ -- 'GHC.Parser.Annotation.AnnCloseP', 'GHC.Parser.Annotation.AnnEqual'
| XFamilyResultSig !(XXFamilyResultSig pass)
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1089,12 +1089,12 @@ data FamilyDecl pass = FamilyDecl
, fdInjectivityAnn :: Maybe (LInjectivityAnn pass) -- optional injectivity ann
}
| XFamilyDecl !(XXFamilyDecl pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
- -- 'ApiAnnotation.AnnData', 'ApiAnnotation.AnnFamily',
- -- 'ApiAnnotation.AnnWhere', 'ApiAnnotation.AnnOpenP',
- -- 'ApiAnnotation.AnnDcolon', 'ApiAnnotation.AnnCloseP',
- -- 'ApiAnnotation.AnnEqual', 'ApiAnnotation.AnnRarrow',
- -- 'ApiAnnotation.AnnVbar'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
+ -- 'GHC.Parser.Annotation.AnnData', 'GHC.Parser.Annotation.AnnFamily',
+ -- 'GHC.Parser.Annotation.AnnWhere', 'GHC.Parser.Annotation.AnnOpenP',
+ -- 'GHC.Parser.Annotation.AnnDcolon', 'GHC.Parser.Annotation.AnnCloseP',
+ -- 'GHC.Parser.Annotation.AnnEqual', 'GHC.Parser.Annotation.AnnRarrow',
+ -- 'GHC.Parser.Annotation.AnnVbar'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1115,8 +1115,8 @@ type LInjectivityAnn pass = Located (InjectivityAnn pass)
-- This will be represented as "InjectivityAnn `r` [`a`, `c`]"
data InjectivityAnn pass
= InjectivityAnn (Located (IdP pass)) [Located (IdP pass)]
- -- ^ - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnRarrow', 'ApiAnnotation.AnnVbar'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnRarrow', 'GHC.Parser.Annotation.AnnVbar'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1256,10 +1256,10 @@ type LHsDerivingClause pass = Located (HsDerivingClause pass)
-- | A single @deriving@ clause of a data declaration.
--
--- - 'ApiAnnotation.AnnKeywordId' :
--- 'ApiAnnotation.AnnDeriving', 'ApiAnnotation.AnnStock',
--- 'ApiAnnotation.AnnAnyClass', 'Api.AnnNewtype',
--- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
+-- - 'GHC.Parser.Annotation.AnnKeywordId' :
+-- 'GHC.Parser.Annotation.AnnDeriving', 'GHC.Parser.Annotation.AnnStock',
+-- 'GHC.Parser.Annotation.AnnAnyClass', 'Api.AnnNewtype',
+-- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose'
data HsDerivingClause pass
-- See Note [Deriving strategies] in GHC.Tc.Deriv
= HsDerivingClause
@@ -1348,7 +1348,7 @@ newOrDataToFlavour DataType = DataTypeFlavour
-- | Located data Constructor Declaration
type LConDecl pass = Located (ConDecl pass)
- -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when
+ -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' when
-- in a GADT constructor list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1369,11 +1369,11 @@ type LConDecl pass = Located (ConDecl pass)
-- Int `MkT` Int :: T Int
-- @
--
--- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
--- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnCLose',
--- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnVbar',
--- 'ApiAnnotation.AnnDarrow','ApiAnnotation.AnnDarrow',
--- 'ApiAnnotation.AnnForall','ApiAnnotation.AnnDot'
+-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen',
+-- 'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnCLose',
+-- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnVbar',
+-- 'GHC.Parser.Annotation.AnnDarrow','GHC.Parser.Annotation.AnnDarrow',
+-- 'GHC.Parser.Annotation.AnnForall','GHC.Parser.Annotation.AnnDot'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1722,7 +1722,7 @@ free-standing `type instance` declaration.
-- | Located Type Family Instance Equation
type LTyFamInstEqn pass = Located (TyFamInstEqn pass)
- -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
+ -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi'
-- when in a list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1781,8 +1781,8 @@ type LTyFamInstDecl pass = Located (TyFamInstDecl pass)
-- | Type Family Instance Declaration
newtype TyFamInstDecl pass = TyFamInstDecl { tfid_eqn :: TyFamInstEqn pass }
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
- -- 'ApiAnnotation.AnnInstance',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
+ -- 'GHC.Parser.Annotation.AnnInstance',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1795,11 +1795,11 @@ type LDataFamInstDecl pass = Located (DataFamInstDecl pass)
newtype DataFamInstDecl pass
= DataFamInstDecl { dfid_eqn :: FamInstEqn pass (HsDataDefn pass) }
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnData',
- -- 'ApiAnnotation.AnnNewType','ApiAnnotation.AnnInstance',
- -- 'ApiAnnotation.AnnDcolon'
- -- 'ApiAnnotation.AnnWhere','ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnData',
+ -- 'GHC.Parser.Annotation.AnnNewType','GHC.Parser.Annotation.AnnInstance',
+ -- 'GHC.Parser.Annotation.AnnDcolon'
+ -- 'GHC.Parser.Annotation.AnnWhere','GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1829,7 +1829,7 @@ data FamEqn pass rhs
, feqn_rhs :: rhs
}
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual'
| XFamEqn !(XXFamEqn pass rhs)
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1854,15 +1854,15 @@ data ClsInstDecl pass
, cid_tyfam_insts :: [LTyFamInstDecl pass] -- Type family instances
, cid_datafam_insts :: [LDataFamInstDecl pass] -- Data family instances
, cid_overlap_mode :: Maybe (Located OverlapMode)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose',
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
}
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnInstance',
- -- 'ApiAnnotation.AnnWhere',
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnInstance',
+ -- 'GHC.Parser.Annotation.AnnWhere',
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XClsInstDecl !(XXClsInstDecl pass)
@@ -2049,10 +2049,10 @@ data DerivDecl pass = DerivDecl
, deriv_strategy :: Maybe (LDerivStrategy pass)
, deriv_overlap_mode :: Maybe (Located OverlapMode)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDeriving',
- -- 'ApiAnnotation.AnnInstance', 'ApiAnnotation.AnnStock',
- -- 'ApiAnnotation.AnnAnyClass', 'Api.AnnNewtype',
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDeriving',
+ -- 'GHC.Parser.Annotation.AnnInstance', 'GHC.Parser.Annotation.AnnStock',
+ -- 'GHC.Parser.Annotation.AnnAnyClass', 'Api.AnnNewtype',
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
}
@@ -2152,8 +2152,8 @@ type LDefaultDecl pass = Located (DefaultDecl pass)
-- | Default Declaration
data DefaultDecl pass
= DefaultDecl (XCDefaultDecl pass) [LHsType pass]
- -- ^ - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnDefault',
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnDefault',
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XDefaultDecl !(XXDefaultDecl pass)
@@ -2197,9 +2197,9 @@ data ForeignDecl pass
, fd_sig_ty :: LHsSigType pass -- sig_ty
, fd_fe :: ForeignExport }
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnForeign',
- -- 'ApiAnnotation.AnnImport','ApiAnnotation.AnnExport',
- -- 'ApiAnnotation.AnnDcolon'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnForeign',
+ -- 'GHC.Parser.Annotation.AnnImport','GHC.Parser.Annotation.AnnExport',
+ -- 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XForeignDecl !(XXForeignDecl pass)
@@ -2339,7 +2339,7 @@ data RuleDecl pass
{ rd_ext :: XHsRule pass
-- ^ After renamer, free-vars from the LHS and RHS
, rd_name :: Located (SourceText,RuleName)
- -- ^ Note [Pragma source text] in GHC.Types.Basic
+ -- ^ Note [Pragma source text] in "GHC.Types.Basic"
, rd_act :: Activation
, rd_tyvs :: Maybe [LHsTyVarBndr () (NoGhcTc pass)]
-- ^ Forall'd type vars
@@ -2350,12 +2350,12 @@ data RuleDecl pass
, rd_rhs :: Located (HsExpr pass)
}
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnTilde',
- -- 'ApiAnnotation.AnnVal',
- -- 'ApiAnnotation.AnnClose',
- -- 'ApiAnnotation.AnnForall','ApiAnnotation.AnnDot',
- -- 'ApiAnnotation.AnnEqual',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnTilde',
+ -- 'GHC.Parser.Annotation.AnnVal',
+ -- 'GHC.Parser.Annotation.AnnClose',
+ -- 'GHC.Parser.Annotation.AnnForall','GHC.Parser.Annotation.AnnDot',
+ -- 'GHC.Parser.Annotation.AnnEqual',
| XRuleDecl !(XXRuleDecl pass)
data HsRuleRn = HsRuleRn NameSet NameSet -- Free-vars from the LHS and RHS
@@ -2379,8 +2379,8 @@ data RuleBndr pass
| RuleBndrSig (XRuleBndrSig pass) (Located (IdP pass)) (HsPatSigType pass)
| XRuleBndr !(XXRuleBndr pass)
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnDcolon','GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -2513,10 +2513,10 @@ data AnnDecl pass = HsAnnotation
(XHsAnnotation pass)
SourceText -- Note [Pragma source text] in GHC.Types.Basic
(AnnProvenance (IdP pass)) (Located (HsExpr pass))
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnType'
- -- 'ApiAnnotation.AnnModule'
- -- 'ApiAnnotation.AnnClose'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnType'
+ -- 'GHC.Parser.Annotation.AnnModule'
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XAnnDecl !(XXAnnDecl pass)
@@ -2567,8 +2567,8 @@ data RoleAnnotDecl pass
= RoleAnnotDecl (XCRoleAnnotDecl pass)
(Located (IdP pass)) -- type constructor
[Located (Maybe Role)] -- optional annotations
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
- -- 'ApiAnnotation.AnnRole'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
+ -- 'GHC.Parser.Annotation.AnnRole'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XRoleAnnotDecl !(XXRoleAnnotDecl pass)
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index e7e71bac2f..20aeb72872 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -74,7 +74,7 @@ import qualified Language.Haskell.TH as TH (Q)
-- | Located Haskell Expression
type LHsExpr p = Located (HsExpr p)
- -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when
+ -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma' when
-- in a list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -280,16 +280,16 @@ data HsExpr p
(MatchGroup p (LHsExpr p))
-- ^ Lambda abstraction. Currently always a single match
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
- -- 'ApiAnnotation.AnnRarrow',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLam',
+ -- 'GHC.Parser.Annotation.AnnRarrow',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsLamCase (XLamCase p) (MatchGroup p (LHsExpr p)) -- ^ Lambda-case
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
- -- 'ApiAnnotation.AnnCase','ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLam',
+ -- 'GHC.Parser.Annotation.AnnCase','GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -302,7 +302,7 @@ data HsExpr p
-- Explicit type argument; e.g f @Int x y
-- NB: Has wildcards, but no implicit quantification
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnAt',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt',
-- | Operator applications:
-- NB Bracketed ops such as (+) come out as Vars.
@@ -318,15 +318,15 @@ data HsExpr p
-- | Negation operator. Contains the negated expression and the name
-- of 'negate'
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnMinus'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnMinus'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| NegApp (XNegApp p)
(LHsExpr p)
(SyntaxExpr p)
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsPar (XPar p)
@@ -341,8 +341,8 @@ data HsExpr p
-- | Used for explicit tuples and sections thereof
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
-- Note [ExplicitTuple]
@@ -353,10 +353,10 @@ data HsExpr p
-- | Used for unboxed sum types
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(#'@,
- -- 'ApiAnnotation.AnnVbar', 'ApiAnnotation.AnnClose' @'#)'@,
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'(#'@,
+ -- 'GHC.Parser.Annotation.AnnVbar', 'GHC.Parser.Annotation.AnnClose' @'#)'@,
--
- -- There will be multiple 'ApiAnnotation.AnnVbar', (1 - alternative) before
+ -- There will be multiple 'GHC.Parser.Annotation.AnnVbar', (1 - alternative) before
-- the expression, (arity - alternative) after it
| ExplicitSum
(XExplicitSum p)
@@ -364,19 +364,19 @@ data HsExpr p
Arity -- Sum arity
(LHsExpr p)
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnCase',
- -- 'ApiAnnotation.AnnOf','ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnClose' @'}'@
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnCase',
+ -- 'GHC.Parser.Annotation.AnnOf','GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCase (XCase p)
(LHsExpr p)
(MatchGroup p (LHsExpr p))
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnIf',
- -- 'ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnThen','ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnElse',
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnIf',
+ -- 'GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnThen','GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnElse',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsIf (XIf p) -- GhcPs: this is a Bool; False <=> do not use
@@ -390,27 +390,27 @@ data HsExpr p
-- | Multi-way if
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnIf'
- -- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose',
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnIf'
+ -- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsMultiIf (XMultiIf p) [LGRHS p (LHsExpr p)]
-- | let(rec)
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLet',
- -- 'ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnClose' @'}'@,'ApiAnnotation.AnnIn'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLet',
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'}'@,'GHC.Parser.Annotation.AnnIn'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsLet (XLet p)
(LHsLocalBinds p)
(LHsExpr p)
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDo',
- -- 'ApiAnnotation.AnnOpen', 'ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnVbar',
- -- 'ApiAnnotation.AnnClose'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDo',
+ -- 'GHC.Parser.Annotation.AnnOpen', 'GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnVbar',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsDo (XDo p) -- Type of the whole expression
@@ -421,8 +421,8 @@ data HsExpr p
-- | Syntactic list: [a,b,c,...]
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
- -- 'ApiAnnotation.AnnClose' @']'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@,
+ -- 'GHC.Parser.Annotation.AnnClose' @']'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
-- See Note [Empty lists]
@@ -434,8 +434,8 @@ data HsExpr p
-- | Record construction
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose' @'}'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| RecordCon
@@ -446,8 +446,8 @@ data HsExpr p
-- | Record update
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose' @'}'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| RecordUpd
@@ -460,7 +460,7 @@ data HsExpr p
-- | Expression with an explicit type signature. @e :: type@
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| ExprWithTySig
@@ -471,9 +471,9 @@ data HsExpr p
-- | Arithmetic sequence
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
- -- 'ApiAnnotation.AnnComma','ApiAnnotation.AnnDotdot',
- -- 'ApiAnnotation.AnnClose' @']'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@,
+ -- 'GHC.Parser.Annotation.AnnComma','GHC.Parser.Annotation.AnnDotdot',
+ -- 'GHC.Parser.Annotation.AnnClose' @']'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| ArithSeq
@@ -487,9 +487,9 @@ data HsExpr p
-----------------------------------------------------------
-- MetaHaskell Extensions
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnOpenE','ApiAnnotation.AnnOpenEQ',
- -- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnCloseQ'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnOpenE','GHC.Parser.Annotation.AnnOpenEQ',
+ -- 'GHC.Parser.Annotation.AnnClose','GHC.Parser.Annotation.AnnCloseQ'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsBracket (XBracket p) (HsBracket p)
@@ -510,8 +510,8 @@ data HsExpr p
[PendingTcSplice] -- _typechecked_ splices to be
-- pasted back in by the desugarer
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsSpliceE (XSpliceE p) (HsSplice p)
@@ -521,8 +521,8 @@ data HsExpr p
-- | @proc@ notation for Arrows
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnProc',
- -- 'ApiAnnotation.AnnRarrow'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnProc',
+ -- 'GHC.Parser.Annotation.AnnRarrow'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsProc (XProc p)
@@ -532,7 +532,7 @@ data HsExpr p
---------------------------------------
-- static pointers extension
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnStatic',
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnStatic',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsStatic (XStatic p) -- Free variables of the body
@@ -581,8 +581,8 @@ data RecordUpdTc = RecordUpdTc
-- | HsWrap appears only in typechecker output
-- Invariant: The contained Expr is *NOT* itself an HsWrap.
--- See Note [Detecting forced eta expansion] in GHC.HsToCore.Expr.
--- This invariant is maintained by GHC.Hs.Utils.mkHsWrap.
+-- See Note [Detecting forced eta expansion] in "GHC.HsToCore.Expr".
+-- This invariant is maintained by 'GHC.Hs.Utils.mkHsWrap'.
-- hs_syn is something like HsExpr or HsCmd
data HsWrap hs_syn = HsWrap HsWrapper -- the wrapper
(hs_syn GhcTc) -- the thing that is wrapped
@@ -684,22 +684,22 @@ data HsPragE p
SourceText -- Note [Pragma source text] in GHC.Types.Basic
StringLiteral -- "set cost centre" SCC pragma
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# CORE'@,
- -- 'ApiAnnotation.AnnVal', 'ApiAnnotation.AnnClose' @'\#-}'@
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{-\# CORE'@,
+ -- 'GHC.Parser.Annotation.AnnVal', 'GHC.Parser.Annotation.AnnClose' @'\#-}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsPragCore (XCoreAnn p)
SourceText -- Note [Pragma source text] in GHC.Types.Basic
StringLiteral -- hdaume: core annotation
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnOpen' @'{-\# GENERATED'@,
- -- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnVal',
- -- 'ApiAnnotation.AnnColon','ApiAnnotation.AnnVal',
- -- 'ApiAnnotation.AnnMinus',
- -- 'ApiAnnotation.AnnVal','ApiAnnotation.AnnColon',
- -- 'ApiAnnotation.AnnVal',
- -- 'ApiAnnotation.AnnClose' @'\#-}'@
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{-\# GENERATED'@,
+ -- 'GHC.Parser.Annotation.AnnVal','GHC.Parser.Annotation.AnnVal',
+ -- 'GHC.Parser.Annotation.AnnColon','GHC.Parser.Annotation.AnnVal',
+ -- 'GHC.Parser.Annotation.AnnMinus',
+ -- 'GHC.Parser.Annotation.AnnVal','GHC.Parser.Annotation.AnnColon',
+ -- 'GHC.Parser.Annotation.AnnVal',
+ -- 'GHC.Parser.Annotation.AnnClose' @'\#-}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsPragTick -- A pragma introduced tick
@@ -725,7 +725,7 @@ type instance XXPragE (GhcPass _) = NoExtCon
-- @ExplicitTuple [Missing ty1, Present a, Missing ty3]@
-- Which in turn stands for @(\x:ty1 \y:ty2. (x,a,y))@
type LHsTupArg id = Located (HsTupArg id)
--- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma'
+-- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1276,9 +1276,9 @@ type LHsCmd id = Located (HsCmd id)
-- | Haskell Command (e.g. a "statement" in an Arrow proc block)
data HsCmd id
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.Annlarrowtail',
- -- 'ApiAnnotation.Annrarrowtail','ApiAnnotation.AnnLarrowtail',
- -- 'ApiAnnotation.AnnRarrowtail'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.Annlarrowtail',
+ -- 'GHC.Parser.Annotation.Annrarrowtail','GHC.Parser.Annotation.AnnLarrowtail',
+ -- 'GHC.Parser.Annotation.AnnRarrowtail'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
= HsCmdArrApp -- Arrow tail, or arrow application (f -< arg)
@@ -1290,8 +1290,8 @@ data HsCmd id
Bool -- True => right-to-left (f -< arg)
-- False => left-to-right (arg >- f)
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpenB' @'(|'@,
- -- 'ApiAnnotation.AnnCloseB' @'|)'@
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenB' @'(|'@,
+ -- 'GHC.Parser.Annotation.AnnCloseB' @'|)'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCmdArrForm -- Command formation, (| e cmd1 .. cmdn |)
@@ -1311,32 +1311,32 @@ data HsCmd id
| HsCmdLam (XCmdLam id)
(MatchGroup id (LHsCmd id)) -- kappa
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
- -- 'ApiAnnotation.AnnRarrow',
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLam',
+ -- 'GHC.Parser.Annotation.AnnRarrow',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCmdPar (XCmdPar id)
(LHsCmd id) -- parenthesised command
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCmdCase (XCmdCase id)
(LHsExpr id)
(MatchGroup id (LHsCmd id)) -- bodies are HsCmd's
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnCase',
- -- 'ApiAnnotation.AnnOf','ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnClose' @'}'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnCase',
+ -- 'GHC.Parser.Annotation.AnnOf','GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCmdLamCase (XCmdLamCase id)
(MatchGroup id (LHsCmd id)) -- bodies are HsCmd's
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLam',
- -- 'ApiAnnotation.AnnCase','ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnClose' @'}'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLam',
+ -- 'GHC.Parser.Annotation.AnnCase','GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1345,28 +1345,28 @@ data HsCmd id
(LHsExpr id) -- predicate
(LHsCmd id) -- then part
(LHsCmd id) -- else part
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnIf',
- -- 'ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnThen','ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnElse',
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnIf',
+ -- 'GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnThen','GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnElse',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCmdLet (XCmdLet id)
(LHsLocalBinds id) -- let(rec)
(LHsCmd id)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLet',
- -- 'ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnClose' @'}'@,'ApiAnnotation.AnnIn'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLet',
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'}'@,'GHC.Parser.Annotation.AnnIn'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsCmdDo (XCmdDo id) -- Type of the whole expression
(Located [CmdLStmt id])
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDo',
- -- 'ApiAnnotation.AnnOpen', 'ApiAnnotation.AnnSemi',
- -- 'ApiAnnotation.AnnVbar',
- -- 'ApiAnnotation.AnnClose'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDo',
+ -- 'GHC.Parser.Annotation.AnnOpen', 'GHC.Parser.Annotation.AnnSemi',
+ -- 'GHC.Parser.Annotation.AnnVbar',
+ -- 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1586,7 +1586,7 @@ type instance XXMatchGroup (GhcPass _) b = NoExtCon
-- | Located Match
type LMatch id body = Located (Match id body)
--- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi' when in a
+-- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' when in a
-- list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1676,10 +1676,10 @@ hsLMatchPats (L _ (Match { m_pats = pats })) = pats
--
-- GRHSs are used both for pattern bindings and for Matches
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnVbar',
--- 'ApiAnnotation.AnnEqual','ApiAnnotation.AnnWhere',
--- 'ApiAnnotation.AnnOpen','ApiAnnotation.AnnClose'
--- 'ApiAnnotation.AnnRarrow','ApiAnnotation.AnnSemi'
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVbar',
+-- 'GHC.Parser.Annotation.AnnEqual','GHC.Parser.Annotation.AnnWhere',
+-- 'GHC.Parser.Annotation.AnnOpen','GHC.Parser.Annotation.AnnClose'
+-- 'GHC.Parser.Annotation.AnnRarrow','GHC.Parser.Annotation.AnnSemi'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
data GRHSs p body
@@ -1826,10 +1826,10 @@ type GhciStmt id = Stmt id (LHsExpr id)
-- The SyntaxExprs in here are used *only* for do-notation and monad
-- comprehensions, which have rebindable syntax. Otherwise they are unused.
-- | API Annotations when in qualifier lists or guards
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnVbar',
--- 'ApiAnnotation.AnnComma','ApiAnnotation.AnnThen',
--- 'ApiAnnotation.AnnBy','ApiAnnotation.AnnBy',
--- 'ApiAnnotation.AnnGroup','ApiAnnotation.AnnUsing'
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVbar',
+-- 'GHC.Parser.Annotation.AnnComma','GHC.Parser.Annotation.AnnThen',
+-- 'GHC.Parser.Annotation.AnnBy','GHC.Parser.Annotation.AnnBy',
+-- 'GHC.Parser.Annotation.AnnGroup','GHC.Parser.Annotation.AnnUsing'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
data StmtLR idL idR body -- body should always be (LHs**** idR)
@@ -1847,7 +1847,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR)
-- For ListComp we use the baked-in 'return'
-- For DoExpr, MDoExpr, we don't apply a 'return' at all
-- See Note [Monad Comprehensions]
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLarrow'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLarrow'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| BindStmt (XBindStmt idL idR body)
@@ -1864,7 +1864,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR)
-- appropriate applicative expression by the desugarer, but it is intended
-- to be invisible in error messages.
--
- -- For full details, see Note [ApplicativeDo] in GHC.Rename.Expr
+ -- For full details, see Note [ApplicativeDo] in "GHC.Rename.Expr"
--
| ApplicativeStmt
(XApplicativeStmt idL idR body) -- Post typecheck, Type of the body
@@ -1880,8 +1880,8 @@ data StmtLR idL idR body -- body should always be (LHs**** idR)
(SyntaxExpr idR) -- The `guard` operator; used only in MonadComp
-- See notes [Monad Comprehensions]
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnLet'
- -- 'ApiAnnotation.AnnOpen' @'{'@,'ApiAnnotation.AnnClose' @'}'@,
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnLet'
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{'@,'GHC.Parser.Annotation.AnnClose' @'}'@,
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| LetStmt (XLetStmt idL idR body) (LHsLocalBindsLR idL idR)
@@ -1919,7 +1919,7 @@ data StmtLR idL idR body -- body should always be (LHs**** idR)
} -- See Note [Monad Comprehensions]
-- Recursive statement (see Note [How RecStmt works] below)
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRec'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRec'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| RecStmt
diff --git a/compiler/GHC/Hs/ImpExp.hs b/compiler/GHC/Hs/ImpExp.hs
index 2257352b63..48534bc910 100644
--- a/compiler/GHC/Hs/ImpExp.hs
+++ b/compiler/GHC/Hs/ImpExp.hs
@@ -46,7 +46,7 @@ One per \tr{import} declaration in a module.
type LImportDecl pass = Located (ImportDecl pass)
-- ^ When in a list this may have
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnSemi'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -59,7 +59,7 @@ data ImportDeclQualifiedStyle
-- | Given two possible located 'qualified' tokens, compute a style
-- (in a conforming Haskell program only one of the two can be not
--- 'Nothing'). This is called from 'GHC.Parser'.
+-- 'Nothing'). This is called from "GHC.Parser".
importDeclQualifiedStyle :: Maybe (Located a)
-> Maybe (Located a)
-> ImportDeclQualifiedStyle
@@ -93,18 +93,18 @@ data ImportDecl pass
}
| XImportDecl !(XXImportDecl pass)
-- ^
- -- 'ApiAnnotation.AnnKeywordId's
+ -- 'GHC.Parser.Annotation.AnnKeywordId's
--
- -- - 'ApiAnnotation.AnnImport'
+ -- - 'GHC.Parser.Annotation.AnnImport'
--
- -- - 'ApiAnnotation.AnnOpen', 'ApiAnnotation.AnnClose' for ideclSource
+ -- - 'GHC.Parser.Annotation.AnnOpen', 'GHC.Parser.Annotation.AnnClose' for ideclSource
--
- -- - 'ApiAnnotation.AnnSafe','ApiAnnotation.AnnQualified',
- -- 'ApiAnnotation.AnnPackageName','ApiAnnotation.AnnAs',
- -- 'ApiAnnotation.AnnVal'
+ -- - 'GHC.Parser.Annotation.AnnSafe','GHC.Parser.Annotation.AnnQualified',
+ -- 'GHC.Parser.Annotation.AnnPackageName','GHC.Parser.Annotation.AnnAs',
+ -- 'GHC.Parser.Annotation.AnnVal'
--
- -- - 'ApiAnnotation.AnnHiding','ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose' attached
+ -- - 'GHC.Parser.Annotation.AnnHiding','GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose' attached
-- to location in ideclHiding
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -186,8 +186,8 @@ data IEWrappedName name
deriving (Eq,Data)
-- | Located name with possible adornment
--- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnType',
--- 'ApiAnnotation.AnnPattern'
+-- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnType',
+-- 'GHC.Parser.Annotation.AnnPattern'
type LIEWrappedName name = Located (IEWrappedName name)
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -196,7 +196,7 @@ type LIEWrappedName name = Located (IEWrappedName name)
type LIE pass = Located (IE pass)
-- ^ When in a list this may have
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -209,8 +209,8 @@ data IE pass
-- ^ Imported or exported Thing with Absent list
--
-- The thing is a Class/Type (can't tell)
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnPattern',
- -- 'ApiAnnotation.AnnType','ApiAnnotation.AnnVal'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnPattern',
+ -- 'GHC.Parser.Annotation.AnnType','GHC.Parser.Annotation.AnnVal'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
-- See Note [Located RdrNames] in GHC.Hs.Expr
@@ -219,9 +219,9 @@ data IE pass
--
-- The thing is a Class/Type and the All refers to methods/constructors
--
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnDotdot','ApiAnnotation.AnnClose',
- -- 'ApiAnnotation.AnnType'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnClose',
+ -- 'GHC.Parser.Annotation.AnnType'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
-- See Note [Located RdrNames] in GHC.Hs.Expr
@@ -235,10 +235,10 @@ data IE pass
--
-- The thing is a Class/Type and the imported or exported things are
-- methods/constructors and record fields; see Note [IEThingWith]
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnClose',
- -- 'ApiAnnotation.AnnComma',
- -- 'ApiAnnotation.AnnType'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnClose',
+ -- 'GHC.Parser.Annotation.AnnComma',
+ -- 'GHC.Parser.Annotation.AnnType'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| IEModuleContents (XIEModuleContents pass) (Located ModuleName)
@@ -246,7 +246,7 @@ data IE pass
--
-- (Export Only)
--
- -- - 'ApiAnnotation.AnnKeywordId's : 'ApiAnnotation.AnnModule'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnModule'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| IEGroup (XIEGroup pass) Int HsDocString -- ^ Doc section heading
diff --git a/compiler/GHC/Hs/Lit.hs b/compiler/GHC/Hs/Lit.hs
index 78155289d0..4396e78004 100644
--- a/compiler/GHC/Hs/Lit.hs
+++ b/compiler/GHC/Hs/Lit.hs
@@ -57,7 +57,7 @@ data HsLit x
-- ^ Packed bytes
| HsInt (XHsInt x) IntegralLit
-- ^ Genuinely an Int; arises from
- -- @GHC.Tc.Deriv.Generate@, and from TRANSLATION
+ -- "GHC.Tc.Deriv.Generate", and from TRANSLATION
| HsIntPrim (XHsIntPrim x) {- SourceText -} Integer
-- ^ literal @Int#@
| HsWordPrim (XHsWordPrim x) {- SourceText -} Integer
diff --git a/compiler/GHC/Hs/Pat.hs b/compiler/GHC/Hs/Pat.hs
index 0e29797b43..adadcdbd7d 100644
--- a/compiler/GHC/Hs/Pat.hs
+++ b/compiler/GHC/Hs/Pat.hs
@@ -82,7 +82,7 @@ type LPat p = XRec p Pat
-- | Pattern
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang'
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
data Pat p
@@ -98,26 +98,26 @@ data Pat p
-- See Note [Located RdrNames] in GHC.Hs.Expr
| LazyPat (XLazyPat p)
(LPat p) -- ^ Lazy Pattern
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnTilde'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| AsPat (XAsPat p)
(Located (IdP p)) (LPat p) -- ^ As pattern
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnAt'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| ParPat (XParPat p)
(LPat p) -- ^ Parenthesised pattern
-- See Note [Parens in HsSyn] in GHC.Hs.Expr
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| BangPat (XBangPat p)
(LPat p) -- ^ Bang pattern
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnBang'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -130,8 +130,8 @@ data Pat p
-- ^ Syntactic List
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
- -- 'ApiAnnotation.AnnClose' @']'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@,
+ -- 'GHC.Parser.Annotation.AnnClose' @']'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -157,9 +157,9 @@ data Pat p
-- will be wrapped in CoPats, no?)
-- ^ Tuple sub-patterns
--
- -- - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpen' @'('@ or @'(#'@,
- -- 'ApiAnnotation.AnnClose' @')'@ or @'#)'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@
| SumPat (XSumPat p) -- after typechecker, types of the alternative
(LPat p) -- Sum sub-pattern
@@ -167,9 +167,9 @@ data Pat p
Arity -- Arity (INVARIANT: ≥ 2)
-- ^ Anonymous sum pattern
--
- -- - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpen' @'(#'@,
- -- 'ApiAnnotation.AnnClose' @'#)'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpen' @'(#'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'#)'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -182,7 +182,7 @@ data Pat p
-- ^ Constructor Pattern
------------ View patterns ---------------
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| ViewPat (XViewPat p) -- The overall type of the pattern
@@ -193,8 +193,8 @@ data Pat p
-- ^ View Pattern
------------ Pattern splices ---------------
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'$('@
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| SplicePat (XSplicePat p)
@@ -220,7 +220,7 @@ data Pat p
-- ^ Natural Pattern
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnVal' @'+'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVal' @'+'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| NPlusKPat (XNPlusKPat p) -- Type of overall pattern
@@ -235,7 +235,7 @@ data Pat p
-- ^ n+k pattern
------------ Pattern type signatures ---------------
- -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+ -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| SigPat (XSigPat p) -- After typechecker: Type
@@ -416,7 +416,7 @@ type HsRecUpdField p = HsRecField' (AmbiguousFieldOcc p) (LHsExpr p)
-- | Haskell Record Field
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnEqual',
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual',
--
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
data HsRecField' id arg = HsRecField {
diff --git a/compiler/GHC/Hs/Type.hs b/compiler/GHC/Hs/Type.hs
index 7ee898a90f..ccf98857f4 100644
--- a/compiler/GHC/Hs/Type.hs
+++ b/compiler/GHC/Hs/Type.hs
@@ -304,7 +304,7 @@ quantified in left-to-right order in kind signatures is nice since:
-- | Located Haskell Context
type LHsContext pass = Located (HsContext pass)
- -- ^ 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnUnit'
+ -- ^ 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnUnit'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
noLHsContext :: LHsContext pass
@@ -320,7 +320,7 @@ type HsContext pass = [LHsType pass]
-- | Located Haskell Type
type LHsType pass = Located (HsType pass)
- -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when
+ -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma' when
-- in a list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -330,7 +330,7 @@ type HsKind pass = HsType pass
-- | Located Haskell Kind
type LHsKind pass = Located (HsKind pass)
- -- ^ 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+ -- ^ 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -646,8 +646,8 @@ data HsTyVarBndr flag pass
(Located (IdP pass))
(LHsKind pass) -- The user-supplied kind signature
-- ^
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
- -- 'ApiAnnotation.AnnDcolon', 'ApiAnnotation.AnnClose'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+ -- 'GHC.Parser.Annotation.AnnDcolon', 'GHC.Parser.Annotation.AnnClose'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -692,9 +692,9 @@ data HsType pass
-- Explicit, user-supplied 'forall a {b} c'
, hst_body :: LHsType pass -- body type
}
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnForall',
- -- 'ApiAnnotation.AnnDot','ApiAnnotation.AnnDarrow'
- -- For details on above see note [Api annotations] in GHC.Parser.Annotation
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnForall',
+ -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDarrow'
+ -- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
| HsQualTy -- See Note [HsType binders]
{ hst_xqual :: XQualTy pass
@@ -708,14 +708,14 @@ data HsType pass
-- Type variable, type constructor, or data constructor
-- see Note [Promotions (HsTyVar)]
-- See Note [Located RdrNames] in GHC.Hs.Expr
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsAppTy (XAppTy pass)
(LHsType pass)
(LHsType pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -727,35 +727,35 @@ data HsType pass
(HsArrow pass)
(LHsType pass) -- function type
(LHsType pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnRarrow',
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow',
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsListTy (XListTy pass)
(LHsType pass) -- Element type
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'['@,
- -- 'ApiAnnotation.AnnClose' @']'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@,
+ -- 'GHC.Parser.Annotation.AnnClose' @']'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsTupleTy (XTupleTy pass)
HsTupleSort
[LHsType pass] -- Element types (length gives arity)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(' or '(#'@,
- -- 'ApiAnnotation.AnnClose' @')' or '#)'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'(' or '(#'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')' or '#)'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsSumTy (XSumTy pass)
[LHsType pass] -- Element types (length gives arity)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'(#'@,
- -- 'ApiAnnotation.AnnClose' '#)'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'(#'@,
+ -- 'GHC.Parser.Annotation.AnnClose' '#)'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsOpTy (XOpTy pass)
(LHsType pass) (Located (IdP pass)) (LHsType pass)
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -764,8 +764,8 @@ data HsType pass
-- Parenthesis preserved for the precedence re-arrangement in
-- GHC.Rename.HsType
-- It's important that a * (b + c) doesn't get rearranged to (a*b) + c!
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -776,14 +776,14 @@ data HsType pass
-- ^
-- > (?x :: ty)
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsStarTy (XStarTy pass)
Bool -- Is this the Unicode variant?
-- Note [HsStarTy]
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
| HsKindSig (XKindSig pass)
(LHsType pass) -- (ty :: kind)
@@ -791,43 +791,43 @@ data HsType pass
-- ^
-- > (ty :: kind)
--
- -- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'('@,
- -- 'ApiAnnotation.AnnDcolon','ApiAnnotation.AnnClose' @')'@
+ -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@,
+ -- 'GHC.Parser.Annotation.AnnDcolon','GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsSpliceTy (XSpliceTy pass)
(HsSplice pass) -- Includes quasi-quotes
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'$('@,
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsDocTy (XDocTy pass)
(LHsType pass) LHsDocString -- A documented type
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsBangTy (XBangTy pass)
HsSrcBang (LHsType pass) -- Bang-style type annotations
- -- ^ - 'ApiAnnotation.AnnKeywordId' :
- -- 'ApiAnnotation.AnnOpen' @'{-\# UNPACK' or '{-\# NOUNPACK'@,
- -- 'ApiAnnotation.AnnClose' @'#-}'@
- -- 'ApiAnnotation.AnnBang' @\'!\'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' :
+ -- 'GHC.Parser.Annotation.AnnOpen' @'{-\# UNPACK' or '{-\# NOUNPACK'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'#-}'@
+ -- 'GHC.Parser.Annotation.AnnBang' @\'!\'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsRecTy (XRecTy pass)
[LConDeclField pass] -- Only in data type declarations
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{'@,
- -- 'ApiAnnotation.AnnClose' @'}'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@,
+ -- 'GHC.Parser.Annotation.AnnClose' @'}'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
-- | HsCoreTy (XCoreTy pass) Type -- An escape hatch for tunnelling a *closed*
-- -- Core Type through HsSyn.
- -- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -835,27 +835,27 @@ data HsType pass
(XExplicitListTy pass)
PromotionFlag -- whether explicitly promoted, for pretty printer
[LHsType pass]
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @"'["@,
- -- 'ApiAnnotation.AnnClose' @']'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @"'["@,
+ -- 'GHC.Parser.Annotation.AnnClose' @']'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsExplicitTupleTy -- A promoted explicit tuple
(XExplicitTupleTy pass)
[LHsType pass]
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @"'("@,
- -- 'ApiAnnotation.AnnClose' @')'@
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @"'("@,
+ -- 'GHC.Parser.Annotation.AnnClose' @')'@
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsTyLit (XTyLit pass) HsTyLit -- A promoted numeric literal.
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| HsWildCardTy (XWildCardTy pass) -- A type wildcard
-- See Note [The wildcard story for types]
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -867,7 +867,7 @@ data NewHsTypeX
= NHsCoreTy Type -- An escape hatch for tunnelling a *closed*
-- Core Type through HsSyn.
deriving Data
- -- ^ - 'ApiAnnotation.AnnKeywordId' : None
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None
instance Outputable NewHsTypeX where
ppr (NHsCoreTy ty) = ppr ty
@@ -1074,7 +1074,7 @@ data HsTupleSort = HsUnboxedTuple
-- | Located Constructor Declaration Field
type LConDeclField pass = Located (ConDeclField pass)
- -- ^ May have 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnComma' when
+ -- ^ May have 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnComma' when
-- in a list
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
@@ -1086,7 +1086,7 @@ data ConDeclField pass -- Record fields have Haddock docs on them
-- ^ See Note [ConDeclField passs]
cd_fld_type :: LBangType pass,
cd_fld_doc :: Maybe LHsDocString }
- -- ^ - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnDcolon'
+ -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon'
-- For details on above see note [Api annotations] in GHC.Parser.Annotation
| XConDeclField !(XXConDeclField pass)
@@ -1556,7 +1556,7 @@ type LFieldOcc pass = Located (FieldOcc pass)
-- renamer, the selector function.
data FieldOcc pass = FieldOcc { extFieldOcc :: XCFieldOcc pass
, rdrNameFieldOcc :: Located RdrName
- -- ^ See Note [Located RdrNames] in GHC.Hs.Expr
+ -- ^ See Note [Located RdrNames] in "GHC.Hs.Expr"
}
| XFieldOcc
@@ -1585,9 +1585,9 @@ mkFieldOcc rdr = FieldOcc noExtField rdr
-- (for unambiguous occurrences) or the typechecker (for ambiguous
-- occurrences).
--
--- See Note [HsRecField and HsRecUpdField] in GHC.Hs.Pat and
--- Note [Disambiguating record fields] in GHC.Tc.Gen.Expr.
--- See Note [Located RdrNames] in GHC.Hs.Expr
+-- See Note [HsRecField and HsRecUpdField] in "GHC.Hs.Pat" and
+-- Note [Disambiguating record fields] in "GHC.Tc.Gen.Expr".
+-- See Note [Located RdrNames] in "GHC.Hs.Expr"
data AmbiguousFieldOcc pass
= Unambiguous (XUnambiguous pass) (Located RdrName)
| Ambiguous (XAmbiguous pass) (Located RdrName)
diff --git a/compiler/GHC/Hs/Utils.hs b/compiler/GHC/Hs/Utils.hs
index 6cad3c71e9..1c8023946c 100644
--- a/compiler/GHC/Hs/Utils.hs
+++ b/compiler/GHC/Hs/Utils.hs
@@ -1002,7 +1002,7 @@ BUT we have a special case when abs_sig is true;
-- | Should we treat this as an unlifted bind? This will be true for any
-- bind that binds an unlifted variable, but we must be careful around
-- AbsBinds. See Note [Unlifted id check in isUnliftedHsBind]. For usage
--- information, see Note [Strict binds check] is GHC.HsToCore.Binds.
+-- information, see Note [Strict binds check] is "GHC.HsToCore.Binds".
isUnliftedHsBind :: HsBind GhcTc -> Bool -- works only over typechecked binds
isUnliftedHsBind bind
| AbsBinds { abs_exports = exports, abs_sig = has_sig } <- bind
diff --git a/compiler/GHC/Parser/Annotation.hs b/compiler/GHC/Parser/Annotation.hs
index e05ac34b75..63cb42845d 100644
--- a/compiler/GHC/Parser/Annotation.hs
+++ b/compiler/GHC/Parser/Annotation.hs
@@ -200,7 +200,7 @@ getAndRemoveAnnotationComments anns span =
-- The annotations, together with original source comments are made
-- available in the @'pm_annotations'@ field of @'GHC.ParsedModule'@.
-- Comments are only retained if @'Opt_KeepRawTokenStream'@ is set in
--- @'DynFlags.DynFlags'@ before parsing.
+-- @'GHC.Driver.Session.DynFlags'@ before parsing.
--
-- The wiki page describing this feature is
-- https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations
@@ -334,11 +334,11 @@ data AnnotationComment =
instance Outputable AnnotationComment where
ppr x = text (show x)
--- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
--- 'ApiAnnotation.AnnClose','ApiAnnotation.AnnComma',
--- 'ApiAnnotation.AnnRarrow'
--- 'ApiAnnotation.AnnTilde'
--- - May have 'ApiAnnotation.AnnComma' when in a list
+-- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen',
+-- 'GHC.Parser.Annotation.AnnClose','GHC.Parser.Annotation.AnnComma',
+-- 'GHC.Parser.Annotation.AnnRarrow'
+-- 'GHC.Parser.Annotation.AnnTilde'
+-- - May have 'GHC.Parser.Annotation.AnnComma' when in a list
type LRdrName = Located RdrName
diff --git a/compiler/GHC/Stg/CSE.hs b/compiler/GHC/Stg/CSE.hs
index d7b0176b71..abe0b6e482 100644
--- a/compiler/GHC/Stg/CSE.hs
+++ b/compiler/GHC/Stg/CSE.hs
@@ -3,6 +3,7 @@
{-|
Note [CSE for Stg]
~~~~~~~~~~~~~~~~~~
+
This module implements a simple common subexpression elimination pass for STG.
This is useful because there are expressions that we want to common up (because
they are operationally equivalent), but that we cannot common up in Core, because
@@ -16,6 +17,7 @@ note [Case 2: CSEing case binders] below.
Note [Case 1: CSEing allocated closures]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
The first kind of CSE opportunity we aim for is generated by this Haskell code:
bar :: a -> (Either Int a, Either Bool a)
@@ -43,6 +45,7 @@ instead.
Note [Case 2: CSEing case binders]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
The second kind of CSE opportunity we aim for is more interesting, and
came up in #9291 and #5344: The Haskell code
@@ -70,6 +73,7 @@ and nothing stops us from transforming that to
Note [StgCse after unarisation]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
Consider two unboxed sum terms:
(# 1 | #) :: (# Int | Int# #)
diff --git a/compiler/GHC/Stg/Lift/Monad.hs b/compiler/GHC/Stg/Lift/Monad.hs
index dcfa0ce644..04a3cbd470 100644
--- a/compiler/GHC/Stg/Lift/Monad.hs
+++ b/compiler/GHC/Stg/Lift/Monad.hs
@@ -156,7 +156,7 @@ instance Outputable FloatLang where
where
(rec, pairs) = decomposeStgBinding bind
--- | Flattens an expression in @['FloatLang']@ into an STG program, see #floats.
+-- | Flattens an expression in @['FloatLang']@ into an STG program, see "GHC.Stg.Lift.Monad#floats".
-- Important pre-conditions: The nesting of opening 'StartBindinGroup's and
-- closing 'EndBindinGroup's is balanced. Also, it is crucial that every binding
-- group has at least one recursive binding inside. Otherwise there's no point
@@ -232,16 +232,16 @@ runLiftM dflags us (LiftM m) = collectFloats (fromOL floats)
addTopStringLit :: OutId -> ByteString -> LiftM ()
addTopStringLit id = LiftM . RWS.tell . unitOL . PlainTopBinding . StgTopStringLit id
--- | Starts a recursive binding group. See #floats# and 'collectFloats'.
+-- | Starts a recursive binding group. See "GHC.Stg.Lift.Monad#floats" and 'collectFloats'.
startBindingGroup :: LiftM ()
startBindingGroup = LiftM $ RWS.tell $ unitOL $ StartBindingGroup
--- | Ends a recursive binding group. See #floats# and 'collectFloats'.
+-- | Ends a recursive binding group. See "GHC.Stg.Lift.Monad#floats" and 'collectFloats'.
endBindingGroup :: LiftM ()
endBindingGroup = LiftM $ RWS.tell $ unitOL $ EndBindingGroup
-- | Lifts a binding to top-level. Depending on whether it's declared inside
--- a recursive RHS (see #floats# and 'collectFloats'), this might be added to
+-- a recursive RHS (see "GHC.Stg.Lift.Monad#floats" and 'collectFloats'), this might be added to
-- an existing recursive top-level binding group.
addLiftedBinding :: OutStgBinding -> LiftM ()
addLiftedBinding = LiftM . RWS.tell . unitOL . LiftedBinding
@@ -289,7 +289,7 @@ withLiftedBndrs :: Traversable f => DIdSet -> f Id -> (f Id -> LiftM a) -> LiftM
withLiftedBndrs abs_ids = runContT . traverse (ContT . withLiftedBndr abs_ids)
-- | Substitutes a binder /occurrence/, which was brought in scope earlier by
--- 'withSubstBndr'\/'withLiftedBndr'.
+-- 'withSubstBndr' \/ 'withLiftedBndr'.
substOcc :: Id -> LiftM Id
substOcc id = LiftM (RWS.asks (lookupIdSubst id . e_subst))
diff --git a/compiler/GHC/Stg/Unarise.hs b/compiler/GHC/Stg/Unarise.hs
index 1cce87248b..aafd28d73b 100644
--- a/compiler/GHC/Stg/Unarise.hs
+++ b/compiler/GHC/Stg/Unarise.hs
@@ -588,7 +588,7 @@ mkUbxSum dc ty_args args0
-- * Literals: 0 or 0.0
-- * Pointers: `ghc-prim:GHC.Prim.Panic.absentSumFieldError`
--
--- See Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make
+-- See Note [aBSENT_SUM_FIELD_ERROR_ID] in "GHC.Core.Make"
--
ubxSumRubbishArg :: SlotTy -> StgArg
ubxSumRubbishArg PtrSlot = StgVarArg aBSENT_SUM_FIELD_ERROR_ID
diff --git a/compiler/GHC/Types/Annotations.hs b/compiler/GHC/Types/Annotations.hs
index 90cbe64f53..e4a89e62e1 100644
--- a/compiler/GHC/Types/Annotations.hs
+++ b/compiler/GHC/Types/Annotations.hs
@@ -34,7 +34,7 @@ import Data.Word ( Word8 )
-- | Represents an annotation after it has been sufficiently desugared from
--- it's initial form of 'HsDecls.AnnDecl'
+-- it's initial form of 'GHC.Hs.Decls.AnnDecl'
data Annotation = Annotation {
ann_target :: CoreAnnTarget, -- ^ The target of the annotation
ann_value :: AnnPayload
diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs
index 82f929fb47..12d54987f5 100644
--- a/compiler/GHC/Types/Basic.hs
+++ b/compiler/GHC/Types/Basic.hs
@@ -152,7 +152,7 @@ instance Outputable LeftOrRight where
-- "real work". So:
-- fib 100 has arity 0
-- \x -> fib x has arity 1
--- See also Note [Definition of arity] in GHC.Core.Opt.Arity
+-- See also Note [Definition of arity] in "GHC.Core.Opt.Arity"
type Arity = Int
-- | Representation Arity
@@ -661,14 +661,14 @@ instance Outputable Origin where
-- instance. See Note [Safe Haskell isSafeOverlap] (in "GHC.Core.InstEnv") for a
-- explanation of the `isSafeOverlap` field.
--
--- - 'ApiAnnotation.AnnKeywordId' :
--- 'ApiAnnotation.AnnOpen' @'\{-\# OVERLAPPABLE'@ or
+-- - 'GHC.Parser.Annotation.AnnKeywordId' :
+-- 'GHC.Parser.Annotation.AnnOpen' @'\{-\# OVERLAPPABLE'@ or
-- @'\{-\# OVERLAPPING'@ or
-- @'\{-\# OVERLAPS'@ or
-- @'\{-\# INCOHERENT'@,
--- 'ApiAnnotation.AnnClose' @`\#-\}`@,
+-- 'GHC.Parser.Annotation.AnnClose' @`\#-\}`@,
--- For details on above see note [Api annotations] in GHC.Parser.Annotation
+-- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
data OverlapFlag = OverlapFlag
{ overlapMode :: OverlapMode
, isSafeOverlap :: Bool
@@ -752,7 +752,7 @@ data OverlapMode -- See Note [Rules for instance lookup] in GHC.Core.InstEnv
-- instance Foo [a]
-- Without the Incoherent flag, we'd complain that
-- instantiating 'b' would change which instance
- -- was chosen. See also note [Incoherent instances] in GHC.Core.InstEnv
+ -- was chosen. See also note [Incoherent instances] in "GHC.Core.InstEnv"
deriving (Eq, Data)
diff --git a/compiler/GHC/Types/CostCentre/State.hs b/compiler/GHC/Types/CostCentre/State.hs
index f53034d700..f1bfa66934 100644
--- a/compiler/GHC/Types/CostCentre/State.hs
+++ b/compiler/GHC/Types/CostCentre/State.hs
@@ -18,7 +18,7 @@ import GHC.Utils.Binary
-- | Per-module state for tracking cost centre indices.
--
--- See documentation of 'CostCentre.cc_flavour' for more details.
+-- See documentation of 'GHC.Types.CostCentre.cc_flavour' for more details.
newtype CostCentreState = CostCentreState (FastStringEnv Int)
-- | Initialize cost centre state.
diff --git a/compiler/GHC/Types/Cpr.hs b/compiler/GHC/Types/Cpr.hs
index 403104b8ad..a884091cef 100644
--- a/compiler/GHC/Types/Cpr.hs
+++ b/compiler/GHC/Types/Cpr.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
-- | Types for the Constructed Product Result lattice. "GHC.Core.Opt.CprAnal" and "GHC.Core.Opt.WorkWrap.Utils"
--- are its primary customers via 'idCprInfo'.
+-- are its primary customers via 'GHC.Types.Id.idCprInfo'.
module GHC.Types.Cpr (
CprResult, topCpr, botCpr, conCpr, asConCpr,
CprType (..), topCprType, botCprType, conCprType,
@@ -113,13 +113,13 @@ trimCprTy :: CprType -> CprType
trimCprTy (CprType arty res) = CprType arty (trimCpr res)
-- | The arity of the wrapped 'CprType' is the arity at which it is safe
--- to unleash. See Note [Understanding DmdType and StrictSig] in GHC.Types.Demand
+-- to unleash. See Note [Understanding DmdType and StrictSig] in "GHC.Types.Demand"
newtype CprSig = CprSig { getCprSig :: CprType }
deriving (Eq, Binary)
-- | Turns a 'CprType' computed for the particular 'Arity' into a 'CprSig'
-- unleashable at that arity. See Note [Understanding DmdType and StrictSig] in
--- Demand
+-- "GHC.Types.Demand"
mkCprSigForArity :: Arity -> CprType -> CprSig
mkCprSigForArity arty ty = CprSig (ensureCprTyArity arty ty)
diff --git a/compiler/GHC/Types/ForeignCall.hs b/compiler/GHC/Types/ForeignCall.hs
index cf3739bfca..b6f0e0b21f 100644
--- a/compiler/GHC/Types/ForeignCall.hs
+++ b/compiler/GHC/Types/ForeignCall.hs
@@ -234,11 +234,11 @@ instance Outputable Header where
-- | A C type, used in CAPI FFI calls
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen' @'{-\# CTYPE'@,
--- 'ApiAnnotation.AnnHeader','ApiAnnotation.AnnVal',
--- 'ApiAnnotation.AnnClose' @'\#-}'@,
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{-\# CTYPE'@,
+-- 'GHC.Parser.Annotation.AnnHeader','GHC.Parser.Annotation.AnnVal',
+-- 'GHC.Parser.Annotation.AnnClose' @'\#-}'@,
--- For details on above see note [Api annotations] in GHC.Parser.Annotation
+-- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
data CType = CType SourceText -- Note [Pragma source text] in GHC.Types.Basic
(Maybe Header) -- header to include for this type
(SourceText,FastString) -- the type itself
diff --git a/compiler/GHC/Types/Id.hs b/compiler/GHC/Types/Id.hs
index ac903fa021..81b7cf20d2 100644
--- a/compiler/GHC/Types/Id.hs
+++ b/compiler/GHC/Types/Id.hs
@@ -11,19 +11,19 @@
-- #name_types#
-- GHC uses several kinds of name internally:
--
--- * 'OccName.OccName': see "OccName#name_types"
+-- * 'GHC.Types.Name.Occurrence.OccName': see "GHC.Types.Name.Occurrence#name_types"
--
--- * 'RdrName.RdrName': see "RdrName#name_types"
+-- * 'GHC.Types.Name.Reader.RdrName': see "GHC.Types.Name.Reader#name_types"
--
--- * 'Name.Name': see "Name#name_types"
+-- * 'GHC.Types.Name.Name': see "GHC.Types.Name#name_types"
--
--- * 'Id.Id' represents names that not only have a 'Name.Name' but also a
--- 'GHC.Core.TyCo.Rep.Type' and some additional details (a 'IdInfo.IdInfo' and
--- one of 'Var.LocalIdDetails' or 'IdInfo.GlobalIdDetails') that are added,
--- modified and inspected by various compiler passes. These 'Var.Var' names
--- may either be global or local, see "Var#globalvslocal"
+-- * 'GHC.Types.Id.Id' represents names that not only have a 'GHC.Types.Name.Name' but also a
+-- 'GHC.Core.TyCo.Rep.Type' and some additional details (a 'GHC.Types.Id.Info.IdInfo' and
+-- one of LocalIdDetails or GlobalIdDetails) that are added,
+-- modified and inspected by various compiler passes. These 'GHC.Types.Var.Var' names
+-- may either be global or local, see "GHC.Types.Var#globalvslocal"
--
--- * 'Var.Var': see "Var#name_types"
+-- * 'GHC.Types.Var.Var': see "GHC.Types.Var#name_types"
module GHC.Types.Id (
-- * The main types
@@ -276,7 +276,7 @@ substitution (which changes the free type variables) is more common.
Anyway, we removed it in March 2008.
-}
--- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal"
+-- | For an explanation of global vs. local 'Id's, see "GHC.Types.Var.Var#globalvslocal"
mkGlobalId :: IdDetails -> Name -> Type -> IdInfo -> Id
mkGlobalId = Var.mkGlobalVar
@@ -289,7 +289,7 @@ mkVanillaGlobalWithInfo :: Name -> Type -> IdInfo -> Id
mkVanillaGlobalWithInfo = mkGlobalId VanillaId
--- | For an explanation of global vs. local 'Id's, see "Var#globalvslocal"
+-- | For an explanation of global vs. local 'Id's, see "GHC.Types.Var#globalvslocal"
mkLocalId :: HasDebugCallStack => Name -> Mult -> Type -> Id
mkLocalId name w ty = ASSERT( not (isCoVarType ty) )
mkLocalIdWithInfo name w ty vanillaIdInfo
@@ -347,7 +347,7 @@ mkSysLocalOrCoVarM :: MonadUnique m => FastString -> Mult -> Type -> m Id
mkSysLocalOrCoVarM fs w ty
= getUniqueM >>= (\uniq -> return (mkSysLocalOrCoVar fs uniq w ty))
--- | Create a user local 'Id'. These are local 'Id's (see "Var#globalvslocal") with a name and location that the user might recognize
+-- | Create a user local 'Id'. These are local 'Id's (see "GHC.Types.Var#globalvslocal") with a name and location that the user might recognize
mkUserLocal :: OccName -> Unique -> Mult -> Type -> SrcSpan -> Id
mkUserLocal occ uniq w ty loc = ASSERT( not (isCoVarType ty) )
mkLocalId (mkInternalName uniq occ loc) w ty
@@ -659,7 +659,7 @@ idFunRepArity :: Id -> RepArity
idFunRepArity x = countFunRepArgs (idArity x) (idType x)
-- | Returns true if an application to n args diverges or throws an exception
--- See Note [Dead ends] in GHC.Types.Demand.
+-- See Note [Dead ends] in "GHC.Types.Demand".
isDeadEndId :: Var -> Bool
isDeadEndId v
| isId v = isDeadEndSig (idStrictness v)
@@ -810,7 +810,7 @@ idOneShotInfo :: Id -> OneShotInfo
idOneShotInfo id = oneShotInfo (idInfo id)
-- | Like 'idOneShotInfo', but taking the Horrible State Hack in to account
--- See Note [The state-transformer hack] in GHC.Core.Opt.Arity
+-- See Note [The state-transformer hack] in "GHC.Core.Opt.Arity"
idStateHackOneShotInfo :: Id -> OneShotInfo
idStateHackOneShotInfo id
| isStateHackType (idType id) = stateHackOneShot
@@ -820,7 +820,7 @@ idStateHackOneShotInfo id
-- This one is the "business end", called externally.
-- It works on type variables as well as Ids, returning True
-- Its main purpose is to encapsulate the Horrible State Hack
--- See Note [The state-transformer hack] in GHC.Core.Opt.Arity
+-- See Note [The state-transformer hack] in "GHC.Core.Opt.Arity"
isOneShotBndr :: Var -> Bool
isOneShotBndr var
| isTyVar var = True
diff --git a/compiler/GHC/Types/Id/Info.hs b/compiler/GHC/Types/Id/Info.hs
index 69a6eeeb2b..b18c634099 100644
--- a/compiler/GHC/Types/Id/Info.hs
+++ b/compiler/GHC/Types/Id/Info.hs
@@ -176,7 +176,7 @@ data IdDetails
-- This only covers /un-lifted/ coercions, of type
-- (t1 ~# t2) or (t1 ~R# t2), not their lifted variants
| JoinId JoinArity -- ^ An 'Id' for a join point taking n arguments
- -- Note [Join points] in GHC.Core
+ -- Note [Join points] in "GHC.Core"
-- | Recursive Selector Parent
data RecSelParent = RecSelData TyCon | RecSelPatSyn PatSyn deriving Eq
@@ -352,7 +352,7 @@ levityInfo = bitfieldGetLevityInfo . bitfield
oneShotInfo :: IdInfo -> OneShotInfo
oneShotInfo = bitfieldGetOneShotInfo . bitfield
--- | 'Id' arity, as computed by 'GHC.Core.Opt.Arity'. Specifies how many arguments
+-- | 'Id' arity, as computed by "GHC.Core.Opt.Arity". Specifies how many arguments
-- this 'Id' has to be applied to before it doesn any meaningful work.
arityInfo :: IdInfo -> ArityInfo
arityInfo = bitfieldGetArityInfo . bitfield
diff --git a/compiler/GHC/Types/Literal.hs b/compiler/GHC/Types/Literal.hs
index 82807ff00c..6f2914a4ec 100644
--- a/compiler/GHC/Types/Literal.hs
+++ b/compiler/GHC/Types/Literal.hs
@@ -256,7 +256,7 @@ instance Eq Literal where
a == b = compare a b == EQ
-- | Needed for the @Ord@ instance of 'AltCon', which in turn is needed in
--- 'TrieMap.CoreMap'.
+-- 'GHC.Data.TrieMap.CoreMap'.
instance Ord Literal where
compare = cmpLit
diff --git a/compiler/GHC/Types/Name.hs b/compiler/GHC/Types/Name.hs
index 41a65dc3b3..9d74dee606 100644
--- a/compiler/GHC/Types/Name.hs
+++ b/compiler/GHC/Types/Name.hs
@@ -14,18 +14,19 @@
-- #name_types#
-- GHC uses several kinds of name internally:
--
--- * 'OccName.OccName': see "OccName#name_types"
+-- * 'GHC.Types.Name.Occurrence.OccName': see "GHC.Types.Name.Occurrence#name_types"
--
--- * 'RdrName.RdrName': see "RdrName#name_types"
+-- * 'GHC.Types.Name.Reader.RdrName': see "GHC.Types.Name.Reader#name_types"
--
--- * 'Name.Name' is the type of names that have had their scoping and binding resolved. They
--- have an 'OccName.OccName' but also a 'Unique.Unique' that disambiguates Names that have
--- the same 'OccName.OccName' and indeed is used for all 'Name.Name' comparison. Names
--- also contain information about where they originated from, see "Name#name_sorts"
+-- * 'GHC.Types.Name.Name' is the type of names that have had their scoping and
+-- binding resolved. They have an 'OccName' but also a 'GHC.Types.Unique.Unique'
+-- that disambiguates Names that have the same 'OccName' and indeed is used for all
+-- 'Name' comparison. Names also contain information about where they originated
+-- from, see "GHC.Types.Name#name_sorts"
--
--- * 'Id.Id': see "Id#name_types"
+-- * 'GHC.Types.Id.Id': see "GHC.Types.Id#name_types"
--
--- * 'Var.Var': see "Var#name_types"
+-- * 'GHC.Types.Var.Var': see "GHC.Types.Var#name_types"
--
-- #name_sorts#
-- Names are one of:
@@ -306,7 +307,7 @@ nameIsLocalOrFrom :: Module -> Name -> Bool
-- each give rise to a fresh module (Ghci1, Ghci2, etc), but they all come
-- from the magic 'interactive' package; and all the details are kept in the
-- TcLclEnv, TcGblEnv, NOT in the HPT or EPT.
--- See Note [The interactive package] in GHC.Driver.Types
+-- See Note [The interactive package] in "GHC.Driver.Types"
nameIsLocalOrFrom from name
| Just mod <- nameModule_maybe name = from == mod || isInteractiveModule mod
diff --git a/compiler/GHC/Types/Name/Env.hs b/compiler/GHC/Types/Name/Env.hs
index 0481e6b520..cf6d853003 100644
--- a/compiler/GHC/Types/Name/Env.hs
+++ b/compiler/GHC/Types/Name/Env.hs
@@ -150,7 +150,7 @@ lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupNameEnv env n)
-- | Deterministic Name Environment
--
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" for explanation why
-- we need DNameEnv.
type DNameEnv a = UniqDFM a
diff --git a/compiler/GHC/Types/Name/Occurrence.hs b/compiler/GHC/Types/Name/Occurrence.hs
index 2062d5449b..b201ab792f 100644
--- a/compiler/GHC/Types/Name/Occurrence.hs
+++ b/compiler/GHC/Types/Name/Occurrence.hs
@@ -12,17 +12,17 @@
-- #name_types#
-- GHC uses several kinds of name internally:
--
--- * 'OccName.OccName' represents names as strings with just a little more information:
+-- * 'GHC.Types.Name.Occurrence.OccName' represents names as strings with just a little more information:
-- the \"namespace\" that the name came from, e.g. the namespace of value, type constructors or
-- data constructors
--
--- * 'RdrName.RdrName': see "RdrName#name_types"
+-- * 'GHC.Types.Name.Reader.RdrName': see "GHC.Types.Name.Reader#name_types"
--
--- * 'Name.Name': see "Name#name_types"
+-- * 'GHC.Types.Name.Name': see "GHC.Types.Name#name_types"
--
--- * 'Id.Id': see "Id#name_types"
+-- * 'GHC.Types.Id.Id': see "GHC.Types.Id#name_types"
--
--- * 'Var.Var': see "Var#name_types"
+-- * 'GHC.Types.Var.Var': see "GHC.Types.Var#name_types"
module GHC.Types.Name.Occurrence (
-- * The 'NameSpace' type
@@ -592,7 +592,7 @@ isDefaultMethodOcc occ =
-- | Is an 'OccName' one of a Typeable @TyCon@ or @Module@ binding?
-- This is needed as these bindings are renamed differently.
--- See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable.
+-- See Note [Grand plan for Typeable] in "GHC.Tc.Instance.Typeable".
isTypeableBindOcc :: OccName -> Bool
isTypeableBindOcc occ =
case occNameString occ of
diff --git a/compiler/GHC/Types/Name/Reader.hs b/compiler/GHC/Types/Name/Reader.hs
index 8cbff02459..b6f4bbce44 100644
--- a/compiler/GHC/Types/Name/Reader.hs
+++ b/compiler/GHC/Types/Name/Reader.hs
@@ -9,18 +9,18 @@
-- #name_types#
-- GHC uses several kinds of name internally:
--
--- * 'OccName.OccName': see "OccName#name_types"
+-- * 'GHC.Types.Name.Occurrence.OccName': see "GHC.Types.Name.Occurrence#name_types"
--
--- * 'RdrName.RdrName' is the type of names that come directly from the parser. They
+-- * 'GHC.Types.Name.Reader.RdrName' is the type of names that come directly from the parser. They
-- have not yet had their scoping and binding resolved by the renamer and can be
--- thought of to a first approximation as an 'OccName.OccName' with an optional module
+-- thought of to a first approximation as an 'GHC.Types.Name.Occurrence.OccName' with an optional module
-- qualifier
--
--- * 'Name.Name': see "Name#name_types"
+-- * 'GHC.Types.Name.Name': see "GHC.Types.Name#name_types"
--
--- * 'Id.Id': see "Id#name_types"
+-- * 'GHC.Types.Id.Id': see "GHC.Types.Id#name_types"
--
--- * 'Var.Var': see "Var#name_types"
+-- * 'GHC.Types.Var.Var': see "GHC.Types.Var#name_types"
module GHC.Types.Name.Reader (
-- * The main type
@@ -110,14 +110,14 @@ import Data.List( sortBy )
-- > `bar`
-- > ( ~ )
--
--- - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnType',
--- 'ApiAnnotation.AnnOpen' @'('@ or @'['@ or @'[:'@,
--- 'ApiAnnotation.AnnClose' @')'@ or @']'@ or @':]'@,,
--- 'ApiAnnotation.AnnBackquote' @'`'@,
--- 'ApiAnnotation.AnnVal'
--- 'ApiAnnotation.AnnTilde',
-
--- For details on above see note [Api annotations] in GHC.Parser.Annotation
+-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnType',
+-- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'['@ or @'[:'@,
+-- 'GHC.Parser.Annotation.AnnClose' @')'@ or @']'@ or @':]'@,,
+-- 'GHC.Parser.Annotation.AnnBackquote' @'`'@,
+-- 'GHC.Parser.Annotation.AnnVal'
+-- 'GHC.Parser.Annotation.AnnTilde',
+
+-- For details on above see note [Api annotations] in "GHC.Parser.Annotation"
data RdrName
= Unqual OccName
-- ^ Unqualified name
@@ -344,7 +344,7 @@ instance Ord RdrName where
-- (@let@, @where@, lambda, @case@).
-- It is keyed by OccName, because we never use it for qualified names
-- We keep the current mapping, *and* the set of all Names in scope
--- Reason: see Note [Splicing Exact names] in GHC.Rename.Env
+-- Reason: see Note [Splicing Exact names] in "GHC.Rename.Env"
data LocalRdrEnv = LRE { lre_env :: OccEnv Name
, lre_in_scope :: NameSet }
@@ -934,7 +934,7 @@ pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt,GlobalRdrElt)]
-- it is in scope qualified an unqualified respectively
--
-- Used only for the 'module M' item in export list;
--- see GHC.Rename.Names.exports_from_avail
+-- see 'GHC.Tc.Gen.Export.exports_from_avail'
pickGREsModExp mod gres = mapMaybe (pickBothGRE mod) gres
pickBothGRE :: ModuleName -> GlobalRdrElt -> Maybe (GlobalRdrElt, GlobalRdrElt)
diff --git a/compiler/GHC/Types/RepType.hs b/compiler/GHC/Types/RepType.hs
index 5c99cc697d..73f35f33cc 100644
--- a/compiler/GHC/Types/RepType.hs
+++ b/compiler/GHC/Types/RepType.hs
@@ -312,7 +312,7 @@ fitsIn ty1 ty2
Note [RuntimeRep and PrimRep]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
This Note describes the relationship between GHC.Types.RuntimeRep
-(of levity-polymorphism fame) and TyCon.PrimRep, as these types
+(of levity-polymorphism fame) and GHC.Core.TyCon.PrimRep, as these types
are closely related.
A "primitive entity" is one that can be
@@ -329,7 +329,7 @@ Examples include:
* ...etc...
The "representation or a primitive entity" specifies what kind of register is
-needed and how many bits are required. The data type TyCon.PrimRep
+needed and how many bits are required. The data type GHC.Core.TyCon.PrimRep
enumerates all the possibilities.
data PrimRep
diff --git a/compiler/GHC/Types/SrcLoc.hs b/compiler/GHC/Types/SrcLoc.hs
index d61c942397..71b74c00d5 100644
--- a/compiler/GHC/Types/SrcLoc.hs
+++ b/compiler/GHC/Types/SrcLoc.hs
@@ -145,7 +145,7 @@ data RealSrcLoc
--
-- Unlike 'RealSrcLoc', it is not affected by #line and {-# LINE ... #-}
-- pragmas. In particular, notice how 'setSrcLoc' and 'resetAlrLastLoc' in
--- GHC.Parser.Lexer update 'PsLoc' preserving 'BufPos'.
+-- "GHC.Parser.Lexer" update 'PsLoc' preserving 'BufPos'.
--
-- The parser guarantees that 'BufPos' are monotonic. See #17632.
newtype BufPos = BufPos { bufPos :: Int }
diff --git a/compiler/GHC/Types/Unique.hs b/compiler/GHC/Types/Unique.hs
index fba286da3f..36d85ff9f2 100644
--- a/compiler/GHC/Types/Unique.hs
+++ b/compiler/GHC/Types/Unique.hs
@@ -67,7 +67,7 @@ module GHC.Types.Unique (
dataConWorkerUnique, dataConTyRepNameUnique,
-- ** Local uniques
- -- | These are exposed exclusively for use by 'VarEnv.uniqAway', which
+ -- | These are exposed exclusively for use by 'GHC.Types.Var.Env.uniqAway', which
-- has rather peculiar needs. See Note [Local uniques].
mkLocalUnique, minLocalUnique, maxLocalUnique
) where
@@ -178,7 +178,7 @@ unpkUnique (MkUnique u)
-- | The interface file symbol-table encoding assumes that known-key uniques fit
-- in 30-bits; verify this.
--
--- See Note [Symbol table representation of names] in GHC.Iface.Binary for details.
+-- See Note [Symbol table representation of names] in "GHC.Iface.Binary" for details.
isValidKnownKeyUnique :: Unique -> Bool
isValidKnownKeyUnique u =
case unpkUnique u of
diff --git a/compiler/GHC/Types/Unique/DSet.hs b/compiler/GHC/Types/Unique/DSet.hs
index 20c571284e..479b69ba0a 100644
--- a/compiler/GHC/Types/Unique/DSet.hs
+++ b/compiler/GHC/Types/Unique/DSet.hs
@@ -4,7 +4,7 @@
-- Specialised deterministic sets, for things with @Uniques@
--
-- Based on 'UniqDFM's (as you would expect).
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why we need it.
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" for explanation why we need it.
--
-- Basically, the things need to be in class 'Uniquable'.
diff --git a/compiler/GHC/Types/Unique/FM.hs b/compiler/GHC/Types/Unique/FM.hs
index 6801489604..fc33e9693f 100644
--- a/compiler/GHC/Types/Unique/FM.hs
+++ b/compiler/GHC/Types/Unique/FM.hs
@@ -358,21 +358,21 @@ nonDetUFMToList (UFM m) = map (\(k, v) -> (getUnique k, v)) $ M.toList m
-- nondeterministic.
-- If you use this please provide a justification why it doesn't introduce
-- nondeterminism.
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" to learn about determinism.
newtype NonDetUniqFM ele = NonDetUniqFM { getNonDet :: UniqFM ele }
deriving (Functor)
-- | Inherently nondeterministic.
-- If you use this please provide a justification why it doesn't introduce
-- nondeterminism.
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" to learn about determinism.
instance Foldable NonDetUniqFM where
foldr f z (NonDetUniqFM (UFM m)) = foldr f z m
-- | Inherently nondeterministic.
-- If you use this please provide a justification why it doesn't introduce
-- nondeterminism.
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM to learn about determinism.
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" to learn about determinism.
instance Traversable NonDetUniqFM where
traverse f (NonDetUniqFM (UFM m)) = NonDetUniqFM . UFM <$> traverse f m
diff --git a/compiler/GHC/Types/Var.hs b/compiler/GHC/Types/Var.hs
index 8baa5750f1..058b6ffc03 100644
--- a/compiler/GHC/Types/Var.hs
+++ b/compiler/GHC/Types/Var.hs
@@ -14,20 +14,20 @@
-- #name_types#
-- GHC uses several kinds of name internally:
--
--- * 'OccName.OccName': see "OccName#name_types"
+-- * 'GHC.Types.Name.Occurrence.OccName': see "GHC.Types.Name.Occurrence#name_types"
--
--- * 'RdrName.RdrName': see "RdrName#name_types"
+-- * 'GHC.Types.Name.Reader.RdrName': see "GHC.Types.Name.Reader#name_types"
--
--- * 'Name.Name': see "Name#name_types"
+-- * 'GHC.Types.Name.Name': see "GHC.Types.Name#name_types"
--
--- * 'Id.Id': see "Id#name_types"
+-- * 'GHC.Types.Id.Id': see "GHC.Types.Id#name_types"
--
--- * 'Var.Var' is a synonym for the 'Id.Id' type but it may additionally
+-- * 'GHC.Types.Var.Var' is a synonym for the 'GHC.Types.Id.Id' type but it may additionally
-- potentially contain type variables, which have a 'GHC.Core.TyCo.Rep.Kind'
-- rather than a 'GHC.Core.TyCo.Rep.Type' and only contain some extra
-- details during typechecking.
--
--- These 'Var.Var' names may either be global or local, see "Var#globalvslocal"
+-- These 'Var' names may either be global or local, see "GHC.Types.Var#globalvslocal"
--
-- #globalvslocal#
-- Global 'Id's and 'Var's are those that are imported or correspond
@@ -443,7 +443,7 @@ updateVarTypeM upd var
-- Is something required to appear in source Haskell ('Required'),
-- permitted by request ('Specified') (visible type application), or
-- prohibited entirely from appearing in source Haskell ('Inferred')?
--- See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in GHC.Core.TyCo.Rep
+-- See Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep"
data ArgFlag = Invisible Specificity
| Required
deriving (Eq, Ord, Data)
@@ -615,7 +615,7 @@ data VarBndr var argf = Bndr var argf
--
-- A 'TyCoVarBinder' is the binder of a ForAllTy
-- It's convenient to define this synonym here rather its natural
--- home in GHC.Core.TyCo.Rep, because it's used in GHC.Core.DataCon.hs-boot
+-- home in "GHC.Core.TyCo.Rep", because it's used in GHC.Core.DataCon.hs-boot
--
-- A 'TyVarBinder' is a binder with only TyVar
type TyCoVarBinder = VarBndr TyCoVar ArgFlag
diff --git a/compiler/GHC/Types/Var/Set.hs b/compiler/GHC/Types/Var/Set.hs
index 8b6bd21f46..c935a336a9 100644
--- a/compiler/GHC/Types/Var/Set.hs
+++ b/compiler/GHC/Types/Var/Set.hs
@@ -62,7 +62,7 @@ import GHC.Utils.Outputable (SDoc)
-- | A non-deterministic Variable Set
--
-- A non-deterministic set of variables.
--- See Note [Deterministic UniqFM] in GHC.Types.Unique.DFM for explanation why it's not
+-- See Note [Deterministic UniqFM] in "GHC.Types.Unique.DFM" for explanation why it's not
-- deterministic and why it matters. Use DVarSet if the set eventually
-- gets converted into a list or folded over in a way where the order
-- changes the generated code, for example when abstracting variables.