diff options
author | Takenobu Tani <takenobu.hs@gmail.com> | 2020-06-09 22:59:05 +0900 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-06-25 03:54:44 -0400 |
commit | 1eb997a84669f158de9dd16a9e54d279cec22293 (patch) | |
tree | 0c917f73815f01bdb4a3055f6eb173429160a723 /compiler/GHC/Tc | |
parent | c7dd6da7e066872a949be7c914cc700182307cd2 (diff) | |
download | haskell-1eb997a84669f158de9dd16a9e54d279cec22293.tar.gz |
Clean up haddock hyperlinks of GHC.* (part2)
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.Iface.*
- GHC.Llvm.*
- GHC.Rename.*
- GHC.Tc.*
- GHC.HsToCore.*
- GHC.StgToCmm.*
- GHC.CmmToAsm.*
- GHC.Runtime.*
- GHC.Unit.*
- GHC.Utils.*
- GHC.SysTools.*
Diffstat (limited to 'compiler/GHC/Tc')
-rw-r--r-- | compiler/GHC/Tc/Deriv/Generate.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Deriv/Utils.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Errors.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/Foreign.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Gen/HsType.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Instance/Class.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Instance/Family.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Instance/Typeable.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Solver.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/Solver/Flatten.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Solver/Interact.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Solver/Monad.hs | 4 | ||||
-rw-r--r-- | compiler/GHC/Tc/TyCl.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Types.hs | 30 | ||||
-rw-r--r-- | compiler/GHC/Tc/Types/Constraint.hs | 22 | ||||
-rw-r--r-- | compiler/GHC/Tc/Types/Evidence.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/Backpack.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/Instantiate.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/Monad.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/TcMType.hs | 6 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/TcType.hs | 14 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/Unify.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Tc/Utils/Zonk.hs | 4 |
23 files changed, 61 insertions, 61 deletions
diff --git a/compiler/GHC/Tc/Deriv/Generate.hs b/compiler/GHC/Tc/Deriv/Generate.hs index 7fa9975790..1fe58c0414 100644 --- a/compiler/GHC/Tc/Deriv/Generate.hs +++ b/compiler/GHC/Tc/Deriv/Generate.hs @@ -13,7 +13,7 @@ -- | Generating derived instance declarations -- --- This module is nominally ``subordinate'' to @GHC.Tc.Deriv@, which is the +-- This module is nominally ``subordinate'' to "GHC.Tc.Deriv", which is the -- ``official'' interface to deriving-related things. -- -- This is where we do all the grimy bindings' generation. diff --git a/compiler/GHC/Tc/Deriv/Utils.hs b/compiler/GHC/Tc/Deriv/Utils.hs index e118c69830..e8f5fe6fc0 100644 --- a/compiler/GHC/Tc/Deriv/Utils.hs +++ b/compiler/GHC/Tc/Deriv/Utils.hs @@ -60,7 +60,7 @@ import qualified GHC.LanguageExtensions as LangExt import GHC.Data.List.SetOps (assocMaybe) -- | To avoid having to manually plumb everything in 'DerivEnv' throughout --- various functions in @GHC.Tc.Deriv@ and @GHC.Tc.Deriv.Infer@, we use 'DerivM', which +-- various functions in "GHC.Tc.Deriv" and "GHC.Tc.Deriv.Infer", we use 'DerivM', which -- is a simple reader around 'TcRn'. type DerivM = ReaderT DerivEnv TcRn diff --git a/compiler/GHC/Tc/Errors.hs b/compiler/GHC/Tc/Errors.hs index 631be3465f..69d4654316 100644 --- a/compiler/GHC/Tc/Errors.hs +++ b/compiler/GHC/Tc/Errors.hs @@ -166,7 +166,7 @@ reportUnsolved wanted -- NB: Type-level holes are OK, because there are no bindings. -- See Note [Deferring coercion errors to runtime] -- Used by solveEqualities for kind equalities --- (see Note [Fail fast on kind errors] in GHC.Tc.Solver) +-- (see Note [Fail fast on kind errors] in "GHC.Tc.Solver") -- and for simplifyDefault. reportAllUnsolved :: WantedConstraints -> TcM () reportAllUnsolved wanted @@ -183,7 +183,7 @@ reportAllUnsolved wanted -- | Report all unsolved goals as warnings (but without deferring any errors to -- run-time). See Note [Safe Haskell Overlapping Instances Implementation] in --- GHC.Tc.Solver +-- "GHC.Tc.Solver" warnAllUnsolved :: WantedConstraints -> TcM () warnAllUnsolved wanted = do { ev_binds <- newTcEvBinds diff --git a/compiler/GHC/Tc/Gen/Foreign.hs b/compiler/GHC/Tc/Gen/Foreign.hs index 9b8f8b29da..df699b9b78 100644 --- a/compiler/GHC/Tc/Gen/Foreign.hs +++ b/compiler/GHC/Tc/Gen/Foreign.hs @@ -7,7 +7,7 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE TypeFamilies #-} --- | Typechecking \tr{foreign} declarations +-- | Typechecking @foreign@ declarations -- -- A foreign declaration is used to either give an externally -- implemented function a Haskell type (and calling interface) or diff --git a/compiler/GHC/Tc/Gen/HsType.hs b/compiler/GHC/Tc/Gen/HsType.hs index d0da974326..68d29f565e 100644 --- a/compiler/GHC/Tc/Gen/HsType.hs +++ b/compiler/GHC/Tc/Gen/HsType.hs @@ -3036,7 +3036,7 @@ zonkAndScopedSort spec_tkvs -- you likely need to push the level before creating whatever type -- gets passed here. Any variable whose level is greater than the -- ambient level but is not selected to be generalized will be --- promoted. (See [Promoting unification variables] in GHC.Tc.Solver +-- promoted. (See [Promoting unification variables] in "GHC.Tc.Solver" -- and Note [Recipe for checking a signature].) -- The resulting KindVar are the variables to -- quantify over, in the correct, well-scoped order. They should @@ -3240,7 +3240,7 @@ data DataSort -- -- 2. @k@ (where @k@ is a bare kind variable; see #12369) -- --- See also Note [Datatype return kinds] in GHC.Tc.TyCl +-- See also Note [Datatype return kinds] in "GHC.Tc.TyCl" checkDataKindSig :: DataSort -> Kind -> TcM () checkDataKindSig data_sort kind = do dflags <- getDynFlags diff --git a/compiler/GHC/Tc/Instance/Class.hs b/compiler/GHC/Tc/Instance/Class.hs index f0c6d17aaa..1df66632a2 100644 --- a/compiler/GHC/Tc/Instance/Class.hs +++ b/compiler/GHC/Tc/Instance/Class.hs @@ -60,7 +60,7 @@ data AssocInstInfo | InClsInst { ai_class :: Class , ai_tyvars :: [TyVar] -- ^ The /scoped/ tyvars of the instance -- Why scoped? See bind_me in - -- GHC.Tc.Validity.checkConsistentFamInst + -- 'GHC.Tc.Validity.checkConsistentFamInst' , ai_inst_env :: VarEnv Type -- ^ Maps /class/ tyvars to their instance types -- See Note [Matching in the consistent-instantiation check] } diff --git a/compiler/GHC/Tc/Instance/Family.hs b/compiler/GHC/Tc/Instance/Family.hs index 448ef0bd8c..698cfa682e 100644 --- a/compiler/GHC/Tc/Instance/Family.hs +++ b/compiler/GHC/Tc/Instance/Family.hs @@ -736,7 +736,7 @@ checkForInjectivityConflicts instEnvs famInst -- this is possible and False if adding this equation would violate injectivity -- annotation. This looks only at the one equation; it does not look for -- interaction between equations. Use checkForInjectivityConflicts for that. --- Does checks (2)-(4) of Note [Verifying injectivity annotation] in GHC.Core.FamInstEnv. +-- Does checks (2)-(4) of Note [Verifying injectivity annotation] in "GHC.Core.FamInstEnv". checkInjectiveEquation :: FamInst -> TcM () checkInjectiveEquation famInst | isTypeFamilyTyCon tycon diff --git a/compiler/GHC/Tc/Instance/Typeable.hs b/compiler/GHC/Tc/Instance/Typeable.hs index bed5779a8d..d49d820a45 100644 --- a/compiler/GHC/Tc/Instance/Typeable.hs +++ b/compiler/GHC/Tc/Instance/Typeable.hs @@ -147,7 +147,7 @@ There are many wrinkles: -- entry-point of this module and is invoked by the typechecker driver in -- 'tcRnSrcDecls'. -- --- See Note [Grand plan for Typeable] in GHC.Tc.Instance.Typeable. +-- See Note [Grand plan for Typeable] in "GHC.Tc.Instance.Typeable". mkTypeableBinds :: TcM TcGblEnv mkTypeableBinds = do { dflags <- getDynFlags @@ -346,7 +346,7 @@ mkPrimTypeableTodos -- The majority of the types we need here are contained in 'primTyCons'. -- However, not all of them: in particular unboxed tuples are absent since we -- don't want to include them in the original name cache. See --- Note [Built-in syntax and the OrigNameCache] in GHC.Iface.Env for more. +-- Note [Built-in syntax and the OrigNameCache] in "GHC.Iface.Env" for more. ghcPrimTypeableTyCons :: [TyCon] ghcPrimTypeableTyCons = concat [ [ runtimeRepTyCon, vecCountTyCon, vecElemTyCon, funTyCon ] diff --git a/compiler/GHC/Tc/Solver.hs b/compiler/GHC/Tc/Solver.hs index 8754ef9fd0..7f60860888 100644 --- a/compiler/GHC/Tc/Solver.hs +++ b/compiler/GHC/Tc/Solver.hs @@ -831,11 +831,11 @@ the let binding. -- | How should we choose which constraints to quantify over? data InferMode = ApplyMR -- ^ Apply the monomorphism restriction, -- never quantifying over any constraints - | EagerDefaulting -- ^ See Note [TcRnExprMode] in GHC.Tc.Module, + | EagerDefaulting -- ^ See Note [TcRnExprMode] in "GHC.Tc.Module", -- the :type +d case; this mode refuses -- to quantify over any defaultable constraint | NoRestrictions -- ^ Quantify over any constraint that - -- satisfies TcType.pickQuantifiablePreds + -- satisfies 'GHC.Tc.Utils.TcType.pickQuantifiablePreds' instance Outputable InferMode where ppr ApplyMR = text "ApplyMR" diff --git a/compiler/GHC/Tc/Solver/Flatten.hs b/compiler/GHC/Tc/Solver/Flatten.hs index 2c3f020f68..c2b68caabb 100644 --- a/compiler/GHC/Tc/Solver/Flatten.hs +++ b/compiler/GHC/Tc/Solver/Flatten.hs @@ -767,7 +767,7 @@ when trying to find derived equalities arising from injectivity. -- If (xi, co) <- flatten mode ev ty, then co :: xi ~r ty -- where r is the role in @ev@. If @mode@ is 'FM_FlattenAll', -- then 'xi' is almost function-free (Note [Almost function-free] --- in GHC.Tc.Types). +-- in "GHC.Tc.Types"). flatten :: FlattenMode -> CtEvidence -> TcType -> TcS (Xi, TcCoercion) flatten mode ev ty diff --git a/compiler/GHC/Tc/Solver/Interact.hs b/compiler/GHC/Tc/Solver/Interact.hs index d95c13cd54..8d4dabc367 100644 --- a/compiler/GHC/Tc/Solver/Interact.hs +++ b/compiler/GHC/Tc/Solver/Interact.hs @@ -2488,7 +2488,7 @@ matchClassInst dflags inerts clas tys loc -- | If a class is "naturally coherent", then we needn't worry at all, in any -- way, about overlapping/incoherent instances. Just solve the thing! -- See Note [Naturally coherent classes] --- See also Note [The equality class story] in GHC.Builtin.Types.Prim. +-- See also Note [The equality class story] in "GHC.Builtin.Types.Prim". naturallyCoherentClass :: Class -> Bool naturallyCoherentClass cls = isCTupleClass cls diff --git a/compiler/GHC/Tc/Solver/Monad.hs b/compiler/GHC/Tc/Solver/Monad.hs index 2ca57e8a23..3500ef4bbe 100644 --- a/compiler/GHC/Tc/Solver/Monad.hs +++ b/compiler/GHC/Tc/Solver/Monad.hs @@ -728,7 +728,7 @@ data InertCans -- See Note [Detailed InertCans Invariants] for more -- failure. -- -- ^ See Note [Safe Haskell Overlapping Instances Implementation] - -- in GHC.Tc.Solver + -- in "GHC.Tc.Solver" , inert_irreds :: Cts -- Irreducible predicates that cannot be made canonical, @@ -2177,7 +2177,7 @@ getNoGivenEqs tclvl skol_tvs -- | Returns Given constraints that might, -- potentially, match the given pred. This is used when checking to see if a -- Given might overlap with an instance. See Note [Instance and Given overlap] --- in GHC.Tc.Solver.Interact. +-- in "GHC.Tc.Solver.Interact" matchableGivens :: CtLoc -> PredType -> InertSet -> Cts matchableGivens loc_w pred_w (IS { inert_cans = inert_cans }) = filterBag matchable_given all_relevant_givens diff --git a/compiler/GHC/Tc/TyCl.hs b/compiler/GHC/Tc/TyCl.hs index edf7456b2c..5970147580 100644 --- a/compiler/GHC/Tc/TyCl.hs +++ b/compiler/GHC/Tc/TyCl.hs @@ -4781,7 +4781,7 @@ wrongKindOfFamily family -- | Produce an error for oversaturated type family equations with too many -- required arguments. --- See Note [Oversaturated type family equations] in GHC.Tc.Validity. +-- See Note [Oversaturated type family equations] in "GHC.Tc.Validity". wrongNumberOfParmsErr :: Arity -> SDoc wrongNumberOfParmsErr max_args = text "Number of parameters must match family declaration; expected" diff --git a/compiler/GHC/Tc/Types.hs b/compiler/GHC/Tc/Types.hs index 1397a3da4b..2fb1a03db0 100644 --- a/compiler/GHC/Tc/Types.hs +++ b/compiler/GHC/Tc/Types.hs @@ -9,7 +9,7 @@ -- | Various types used during typechecking. -- --- Please see GHC.Tc.Utils.Monad as well for operations on these types. You probably +-- Please see "GHC.Tc.Utils.Monad" as well for operations on these types. You probably -- want to import it, instead of this module. -- -- All the monads exported here are built on top of the same IOEnv monad. The @@ -144,14 +144,14 @@ import qualified Language.Haskell.TH as TH -- | A 'NameShape' is a substitution on 'Name's that can be used -- to refine the identities of a hole while we are renaming interfaces --- (see 'GHC.Iface.Rename'). Specifically, a 'NameShape' for +-- (see "GHC.Iface.Rename"). Specifically, a 'NameShape' for -- 'ns_module_name' @A@, defines a mapping from @{A.T}@ -- (for some 'OccName' @T@) to some arbitrary other 'Name'. -- -- The most intruiging thing about a 'NameShape', however, is -- how it's constructed. A 'NameShape' is *implied* by the -- exported 'AvailInfo's of the implementor of an interface: --- if an implementor of signature @<H>@ exports @M.T@, you implicitly +-- if an implementor of signature @\<H>@ exports @M.T@, you implicitly -- define a substitution from @{H.T}@ to @M.T@. So a 'NameShape' -- is computed from the list of 'AvailInfo's that are exported -- by the implementation of a module, or successively merged @@ -419,7 +419,7 @@ data TcGblEnv tcg_fix_env :: FixityEnv, -- ^ Just for things in this module tcg_field_env :: RecFieldEnv, -- ^ Just for things in this module - -- See Note [The interactive package] in GHC.Driver.Types + -- See Note [The interactive package] in "GHC.Driver.Types" tcg_type_env :: TypeEnv, -- ^ Global type env for the module we are compiling now. All @@ -430,7 +430,7 @@ data TcGblEnv -- move to the global envt during zonking) -- -- NB: for what "things in this module" means, see - -- Note [The interactive package] in GHC.Driver.Types + -- Note [The interactive package] in "GHC.Driver.Types" tcg_type_env_var :: TcRef TypeEnv, -- Used only to initialise the interface-file @@ -477,7 +477,7 @@ data TcGblEnv -- (tcRnExports) -- - imp_mods is used to compute usage info (mkIfaceTc, deSugar) -- - imp_trust_own_pkg is used for Safe Haskell in interfaces - -- (mkIfaceTc, as well as in GHC.Driver.Main) + -- (mkIfaceTc, as well as in "GHC.Driver.Main") -- - To create the Dependencies field in interface (mkDependencies) -- These three fields track unused bindings and imports @@ -487,7 +487,7 @@ data TcGblEnv tcg_keep :: TcRef NameSet, tcg_th_used :: TcRef Bool, - -- ^ @True@ <=> Template Haskell syntax used. + -- ^ @True@ \<=> Template Haskell syntax used. -- -- We need this so that we can generate a dependency on the -- Template Haskell package, because the desugarer is going @@ -496,7 +496,7 @@ data TcGblEnv -- mutable variable. tcg_th_splice_used :: TcRef Bool, - -- ^ @True@ <=> A Template Haskell splice was used. + -- ^ @True@ \<=> A Template Haskell splice was used. -- -- Splices disable recompilation avoidance (see #481) @@ -523,7 +523,7 @@ data TcGblEnv -- voluminous and are needed if you want to report unused imports tcg_rn_decls :: Maybe (HsGroup GhcRn), - -- ^ Renamed decls, maybe. @Nothing@ <=> Don't retain renamed + -- ^ Renamed decls, maybe. @Nothing@ \<=> Don't retain renamed -- decls. tcg_dependent_files :: TcRef [FilePath], -- ^ dependencies from addDependentFile @@ -1059,7 +1059,7 @@ data ArrowCtxt -- Note [Escaping the arrow scope] -- | A typecheckable thing available in a local context. Could be -- 'AGlobal' 'TyThing', but also lexically scoped variables, etc. --- See 'GHC.Tc.Utils.Env' for how to retrieve a 'TyThing' given a 'Name'. +-- See "GHC.Tc.Utils.Env" for how to retrieve a 'TyThing' given a 'Name'. data TcTyThing = AGlobal TyThing -- Used only in the return type of a lookup @@ -1112,9 +1112,9 @@ instance Outputable TcTyThing where -- Debugging only -- | IdBindingInfo describes how an Id is bound. -- -- It is used for the following purposes: --- a) for static forms in GHC.Tc.Gen.Expr.checkClosedInStaticForm and +-- a) for static forms in 'GHC.Tc.Gen.Expr.checkClosedInStaticForm' and -- b) to figure out when a nested binding can be generalised, --- in GHC.Tc.Gen.Bind.decideGeneralisationPlan. +-- in 'GHC.Tc.Gen.Bind.decideGeneralisationPlan'. -- data IdBindingInfo -- See Note [Meaning of IdBindingInfo and ClosedTypeId] = NotLetBound @@ -1336,7 +1336,7 @@ data ImportAvails -- = ModuleEnv [ImportedModsVal], -- ^ Domain is all directly-imported modules -- - -- See the documentation on ImportedModsVal in GHC.Driver.Types for the + -- See the documentation on ImportedModsVal in "GHC.Driver.Types" for the -- meaning of the fields. -- -- We need a full ModuleEnv rather than a ModuleNameEnv here, @@ -1368,13 +1368,13 @@ data ImportAvails -- where True for the bool indicates the package is required to be -- trusted is the more logical design, doing so complicates a lot -- of code not concerned with Safe Haskell. - -- See Note [Tracking Trust Transitively] in GHC.Rename.Names + -- See Note [Tracking Trust Transitively] in "GHC.Rename.Names" imp_trust_own_pkg :: Bool, -- ^ Do we require that our own package is trusted? -- This is to handle efficiently the case where a Safe module imports -- a Trustworthy module that resides in the same package as it. - -- See Note [Trust Own Package] in GHC.Rename.Names + -- See Note [Trust Own Package] in "GHC.Rename.Names" imp_orphs :: [Module], -- ^ Orphan modules below us in the import tree (and maybe including diff --git a/compiler/GHC/Tc/Types/Constraint.hs b/compiler/GHC/Tc/Types/Constraint.hs index 0f95d9f133..45266c831e 100644 --- a/compiler/GHC/Tc/Types/Constraint.hs +++ b/compiler/GHC/Tc/Types/Constraint.hs @@ -484,12 +484,12 @@ tyCoVarsOfCt :: Ct -> TcTyCoVarSet tyCoVarsOfCt = fvVarSet . tyCoFVsOfCt -- | Returns free variables of constraints as a deterministically ordered. --- list. See Note [Deterministic FV] in GHC.Utils.FV. +-- list. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoVarsOfCtList :: Ct -> [TcTyCoVar] tyCoVarsOfCtList = fvVarList . tyCoFVsOfCt -- | Returns free variables of constraints as a composable FV computation. --- See Note [Deterministic FV] in GHC.Utils.FV. +-- See Note [Deterministic FV] in "GHC.Utils.FV". tyCoFVsOfCt :: Ct -> FV tyCoFVsOfCt ct = tyCoFVsOfType (ctPred ct) -- This must consult only the ctPred, so that it gets *tidied* fvs if the @@ -497,34 +497,34 @@ tyCoFVsOfCt ct = tyCoFVsOfType (ctPred ct) -- fields of the Ct, only the predicate in the CtEvidence. -- | Returns free variables of a bag of constraints as a non-deterministic --- set. See Note [Deterministic FV] in GHC.Utils.FV. +-- set. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoVarsOfCts :: Cts -> TcTyCoVarSet tyCoVarsOfCts = fvVarSet . tyCoFVsOfCts -- | Returns free variables of a bag of constraints as a deterministically --- ordered list. See Note [Deterministic FV] in GHC.Utils.FV. +-- ordered list. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoVarsOfCtsList :: Cts -> [TcTyCoVar] tyCoVarsOfCtsList = fvVarList . tyCoFVsOfCts -- | Returns free variables of a bag of constraints as a composable FV --- computation. See Note [Deterministic FV] in GHC.Utils.FV. +-- computation. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoFVsOfCts :: Cts -> FV tyCoFVsOfCts = foldr (unionFV . tyCoFVsOfCt) emptyFV -- | Returns free variables of WantedConstraints as a non-deterministic --- set. See Note [Deterministic FV] in GHC.Utils.FV. +-- set. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet -- Only called on *zonked* things, hence no need to worry about flatten-skolems tyCoVarsOfWC = fvVarSet . tyCoFVsOfWC -- | Returns free variables of WantedConstraints as a deterministically --- ordered list. See Note [Deterministic FV] in GHC.Utils.FV. +-- ordered list. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] -- Only called on *zonked* things, hence no need to worry about flatten-skolems tyCoVarsOfWCList = fvVarList . tyCoFVsOfWC -- | Returns free variables of WantedConstraints as a composable FV --- computation. See Note [Deterministic FV] in GHC.Utils.FV. +-- computation. See Note [Deterministic FV] in "GHC.Utils.FV". tyCoFVsOfWC :: WantedConstraints -> FV -- Only called on *zonked* things, hence no need to worry about flatten-skolems tyCoFVsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_holes = holes }) @@ -533,7 +533,7 @@ tyCoFVsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_holes = holes }) tyCoFVsOfBag tyCoFVsOfHole holes -- | Returns free variables of Implication as a composable FV computation. --- See Note [Deterministic FV] in GHC.Utils.FV. +-- See Note [Deterministic FV] in "GHC.Utils.FV". tyCoFVsOfImplic :: Implication -> FV -- Only called on *zonked* things, hence no need to worry about flatten-skolems tyCoFVsOfImplic (Implic { ic_skols = skols @@ -1380,7 +1380,7 @@ data TcEvDest | HoleDest CoercionHole -- ^ fill in this hole with the evidence -- HoleDest is always used for type-equalities - -- See Note [Coercion holes] in GHC.Core.TyCo.Rep + -- See Note [Coercion holes] in "GHC.Core.TyCo.Rep" data CtEvidence = CtGiven -- Truly given, not depending on subgoals @@ -1539,7 +1539,7 @@ ctEvFlavour (CtDerived {}) = Derived -- | Whether or not one 'Ct' can rewrite another is determined by its -- flavour and its equality relation. See also --- Note [Flavours with roles] in GHC.Tc.Solver.Monad +-- Note [Flavours with roles] in "GHC.Tc.Solver.Monad" type CtFlavourRole = (CtFlavour, EqRel) -- | Extract the flavour, role, and boxity from a 'CtEvidence' diff --git a/compiler/GHC/Tc/Types/Evidence.hs b/compiler/GHC/Tc/Types/Evidence.hs index 5b33394136..ccc25c209d 100644 --- a/compiler/GHC/Tc/Types/Evidence.hs +++ b/compiler/GHC/Tc/Types/Evidence.hs @@ -1026,7 +1026,7 @@ instance Outputable EvTypeable where -- expect the 'Type' to have the form `IP sym ty` or `IsLabel sym ty`, -- and return a 'Coercion' `co :: IP sym ty ~ ty` or -- `co :: IsLabel sym ty ~ Proxy# sym -> ty`. See also --- Note [Type-checking overloaded labels] in GHC.Tc.Gen.Expr. +-- Note [Type-checking overloaded labels] in "GHC.Tc.Gen.Expr". unwrapIP :: Type -> CoercionR unwrapIP ty = case unwrapNewTyCon_maybe tc of diff --git a/compiler/GHC/Tc/Utils/Backpack.hs b/compiler/GHC/Tc/Utils/Backpack.hs index 72a1aee55d..f90c6923c8 100644 --- a/compiler/GHC/Tc/Utils/Backpack.hs +++ b/compiler/GHC/Tc/Utils/Backpack.hs @@ -256,7 +256,7 @@ requirementMerges pkgstate mod_name = -- import A -- -- unit q where --- dependency p[A=<A>,B=<B>] +-- dependency p[A=\<A>,B=\<B>] -- signature A -- signature B -- diff --git a/compiler/GHC/Tc/Utils/Instantiate.hs b/compiler/GHC/Tc/Utils/Instantiate.hs index e6f1917331..e7e5c9dc09 100644 --- a/compiler/GHC/Tc/Utils/Instantiate.hs +++ b/compiler/GHC/Tc/Utils/Instantiate.hs @@ -560,7 +560,7 @@ tcSyntaxName :: CtOrigin -> TcM (Name, HsExpr GhcTc) -- ^ (Standard name, suitable expression) -- USED ONLY FOR CmdTop (sigh) *** --- See Note [CmdSyntaxTable] in GHC.Hs.Expr +-- See Note [CmdSyntaxTable] in "GHC.Hs.Expr" tcSyntaxName orig ty (std_nm, HsVar _ (L _ user_nm)) | std_nm == user_nm diff --git a/compiler/GHC/Tc/Utils/Monad.hs b/compiler/GHC/Tc/Utils/Monad.hs index dc7994a62b..c65879a8b4 100644 --- a/compiler/GHC/Tc/Utils/Monad.hs +++ b/compiler/GHC/Tc/Utils/Monad.hs @@ -1519,7 +1519,7 @@ newTcEvBinds = do { binds_ref <- newTcRef emptyEvBindMap , ebv_uniq = uniq }) } -- | Creates an EvBindsVar incapable of holding any bindings. It still --- tracks covar usages (see comments on ebv_tcvs in GHC.Tc.Types.Evidence), thus +-- tracks covar usages (see comments on ebv_tcvs in "GHC.Tc.Types.Evidence"), thus -- must be made monadically newNoTcEvBinds :: TcM EvBindsVar newNoTcEvBinds diff --git a/compiler/GHC/Tc/Utils/TcMType.hs b/compiler/GHC/Tc/Utils/TcMType.hs index d2afbfb4ca..34e4bfe0bb 100644 --- a/compiler/GHC/Tc/Utils/TcMType.hs +++ b/compiler/GHC/Tc/Utils/TcMType.hs @@ -304,7 +304,7 @@ predTypeOccName ty = case classifyPredType ty of -- -- This is monadic to look up the 'TcLclEnv', which is used to initialize -- 'ic_env', and to set the -Winaccessible-code flag. See --- Note [Avoid -Winaccessible-code when deriving] in GHC.Tc.TyCl.Instance. +-- Note [Avoid -Winaccessible-code when deriving] in "GHC.Tc.TyCl.Instance". newImplication :: TcM Implication newImplication = do env <- getLclEnv @@ -609,12 +609,12 @@ tcInstSkolTyVarsAt lvl overlappable subst tvs freshenTyVarBndrs :: [TyVar] -> TcM (TCvSubst, [TyVar]) -- ^ Give fresh uniques to a bunch of TyVars, but they stay -- as TyVars, rather than becoming TcTyVars --- Used in GHC.Tc.Instance.Family.newFamInst, and Inst.newClsInst +-- Used in 'GHC.Tc.Instance.Family.newFamInst', and 'GHC.Tc.Utils.Instantiate.newClsInst' freshenTyVarBndrs = freshenTyCoVars mkTyVar freshenCoVarBndrsX :: TCvSubst -> [CoVar] -> TcM (TCvSubst, [CoVar]) -- ^ Give fresh uniques to a bunch of CoVars --- Used in GHC.Tc.Instance.Family.newFamInst +-- Used in "GHC.Tc.Instance.Family.newFamInst" freshenCoVarBndrsX subst = freshenTyCoVarsX mkCoVar subst ------------------ diff --git a/compiler/GHC/Tc/Utils/TcType.hs b/compiler/GHC/Tc/Utils/TcType.hs index bf6967dccf..280144ac00 100644 --- a/compiler/GHC/Tc/Utils/TcType.hs +++ b/compiler/GHC/Tc/Utils/TcType.hs @@ -7,7 +7,7 @@ {-# LANGUAGE CPP, ScopedTypeVariables, MultiWayIf, FlexibleContexts #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} --- | Types used in the typechecker} +-- | Types used in the typechecker -- -- This module provides the Type interface for front-end parts of the -- compiler. These parts @@ -366,7 +366,7 @@ type TcDTyCoVarSet = DTyCoVarSet ********************************************************************* -} -- | An expected type to check against during type-checking. --- See Note [ExpType] in GHC.Tc.Utils.TcMType, where you'll also find manipulators. +-- See Note [ExpType] in "GHC.Tc.Utils.TcMType", where you'll also find manipulators. data ExpType = Check TcType | Infer !InferResult @@ -417,7 +417,7 @@ mkCheckExpType = Check -- You'll also get three multiplicities back: one for each function arrow. See -- also Note [Linear types] in Multiplicity. -- --- This is defined here to avoid defining it in GHC.Tc.Gen.Expr boot file. +-- This is defined here to avoid defining it in "GHC.Tc.Gen.Expr" boot file. data SyntaxOpType = SynAny -- ^ Any type | SynRho -- ^ A rho type, skolemised or instantiated as appropriate @@ -757,8 +757,8 @@ promoteSkolemsX tclvl = mapAccumL (promoteSkolemX tclvl) -- -- This is important for its use in deciding termination of type -- instances (see #11581). E.g. --- type instance G [Int] = ...(F Int <big type>)... --- we don't need to take <big type> into account when asking if +-- type instance G [Int] = ...(F Int \<big type>)... +-- we don't need to take \<big type> into account when asking if -- the calls on the RHS are smaller than the LHS tcTyFamInsts :: Type -> [(TyCon, [Type])] tcTyFamInsts = map (\(_,b,c) -> (b,c)) . tcTyFamInstsAndVis @@ -1846,7 +1846,7 @@ isImprovementPred ty -- a ~R ...(N a)... -- Not definitely insoluble -- -- Perhaps newtype N a = MkN Int -- See Note [Occurs check error] in --- GHC.Tc.Solver.Canonical for the motivation for this function. +-- "GHC.Tc.Solver.Canonical" for the motivation for this function. isInsolubleOccursCheck :: EqRel -> TcTyVar -> TcType -> Bool isInsolubleOccursCheck eq_rel tv ty = go ty @@ -2104,7 +2104,7 @@ isRigidTy ty -- | Is this type *almost function-free*? See Note [Almost function-free] --- in GHC.Tc.Types +-- in "GHC.Tc.Types" isAlmostFunctionFree :: TcType -> Bool isAlmostFunctionFree ty | Just ty' <- tcView ty = isAlmostFunctionFree ty' isAlmostFunctionFree (TyVarTy {}) = True diff --git a/compiler/GHC/Tc/Utils/Unify.hs b/compiler/GHC/Tc/Utils/Unify.hs index a7787dd4ea..5d7afcf057 100644 --- a/compiler/GHC/Tc/Utils/Unify.hs +++ b/compiler/GHC/Tc/Utils/Unify.hs @@ -775,7 +775,7 @@ tcEqMult origin w_actual w_expected = do %********************************************************************* -} -- | Infer a type using a fresh ExpType --- See also Note [ExpType] in GHC.Tc.Utils.TcMType +-- See also Note [ExpType] in "GHC.Tc.Utils.TcMType" tcInfer :: (ExpSigmaType -> TcM a) -> TcM (a, TcSigmaType) tcInfer tc_check = do { res_ty <- newInferExpType diff --git a/compiler/GHC/Tc/Utils/Zonk.hs b/compiler/GHC/Tc/Utils/Zonk.hs index 8267cb125a..17bdb42c3a 100644 --- a/compiler/GHC/Tc/Utils/Zonk.hs +++ b/compiler/GHC/Tc/Utils/Zonk.hs @@ -29,7 +29,7 @@ module GHC.Tc.Utils.Zonk ( -- * Zonking -- | For a description of "zonking", see Note [What is zonking?] - -- in GHC.Tc.Utils.TcMType + -- in "GHC.Tc.Utils.TcMType" zonkTopDecls, zonkTopExpr, zonkTopLExpr, zonkTopBndrs, ZonkEnv, ZonkFlexi(..), emptyZonkEnv, mkEmptyZonkEnv, initZonkEnv, @@ -203,7 +203,7 @@ the environment manipulation is tiresome. -- Confused by zonking? See Note [What is zonking?] in GHC.Tc.Utils.TcMType. -- | See Note [The ZonkEnv] --- Confused by zonking? See Note [What is zonking?] in GHC.Tc.Utils.TcMType. +-- Confused by zonking? See Note [What is zonking?] in "GHC.Tc.Utils.TcMType". data ZonkEnv -- See Note [The ZonkEnv] = ZonkEnv { ze_flexi :: ZonkFlexi , ze_tv_env :: TyCoVarEnv TyCoVar |