summaryrefslogtreecommitdiff
path: root/compiler/GHC/Types
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 /compiler/GHC/Types
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
Diffstat (limited to 'compiler/GHC/Types')
-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
19 files changed, 84 insertions, 83 deletions
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.