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 | |
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')
57 files changed, 146 insertions, 143 deletions
diff --git a/compiler/GHC/CmmToAsm/CFG.hs b/compiler/GHC/CmmToAsm/CFG.hs index aea78e278f..5db10ce93f 100644 --- a/compiler/GHC/CmmToAsm/CFG.hs +++ b/compiler/GHC/CmmToAsm/CFG.hs @@ -107,7 +107,7 @@ instance Outputable EdgeWeight where type EdgeInfoMap edgeInfo = LabelMap (LabelMap edgeInfo) -- | A control flow graph where edges have been annotated with a weight. --- Implemented as IntMap (IntMap <edgeData>) +-- Implemented as IntMap (IntMap \<edgeData>) -- We must uphold the invariant that for each edge A -> B we must have: -- A entry B in the outer map. -- A entry B in the map we get when looking up A. @@ -148,7 +148,7 @@ instance Outputable CfgEdge where -- | Can we trace back a edge to a specific Cmm Node -- or has it been introduced during assembly codegen. We use this to maintain -- some information which would otherwise be lost during the --- Cmm <-> asm transition. +-- Cmm \<-> asm transition. -- See also Note [Inverting Conditional Branches] data TransitionSource = CmmSource { trans_cmmNode :: (CmmNode O C) diff --git a/compiler/GHC/CmmToAsm/Dwarf/Constants.hs b/compiler/GHC/CmmToAsm/Dwarf/Constants.hs index e550813be1..67137e1c57 100644 --- a/compiler/GHC/CmmToAsm/Dwarf/Constants.hs +++ b/compiler/GHC/CmmToAsm/Dwarf/Constants.hs @@ -1,5 +1,5 @@ -- | Constants describing the DWARF format. Most of this simply --- mirrors /usr/include/dwarf.h. +-- mirrors \/usr\/include\/dwarf.h. module GHC.CmmToAsm.Dwarf.Constants where diff --git a/compiler/GHC/CmmToAsm/Monad.hs b/compiler/GHC/CmmToAsm/Monad.hs index 258acae40c..88d8f4b17c 100644 --- a/compiler/GHC/CmmToAsm/Monad.hs +++ b/compiler/GHC/CmmToAsm/Monad.hs @@ -97,7 +97,7 @@ data NcgImpl statics instr jumpDest = NcgImpl { -- and Note [Unwinding information in the NCG] in this module. invertCondBranches :: Maybe CFG -> LabelMap RawCmmStatics -> [NatBasicBlock instr] -> [NatBasicBlock instr] - -- ^ Turn the sequence of `jcc l1; jmp l2` into `jncc l2; <block_l1>` + -- ^ Turn the sequence of @jcc l1; jmp l2@ into @jncc l2; \<block_l1>@ -- when possible. } diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs index ec77d91185..a5016abc6f 100644 --- a/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs +++ b/compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs @@ -5,6 +5,7 @@ -- Handling of join points -- ~~~~~~~~~~~~~~~~~~~~~~~ -- +-- @ -- B1: B2: -- ... ... -- RELOAD SLOT(0), %r1 RELOAD SLOT(0), %r1 @@ -14,9 +15,11 @@ -- B3: ... C ... -- RELOAD SLOT(0), %r1 -- ... +-- @ -- -- The Plan -- ~~~~~~~~ +-- -- As long as %r1 hasn't been written to in A, B or C then we don't need -- the reload in B3. -- diff --git a/compiler/GHC/CmmToAsm/SPARC/CodeGen/Base.hs b/compiler/GHC/CmmToAsm/SPARC/CodeGen/Base.hs index 34ee34295d..0662fd06af 100644 --- a/compiler/GHC/CmmToAsm/SPARC/CodeGen/Base.hs +++ b/compiler/GHC/CmmToAsm/SPARC/CodeGen/Base.hs @@ -45,7 +45,7 @@ data CondCode = CondCode Bool Cond InstrBlock --- | a.k.a "Register64" +-- | a.k.a \"Register64\" -- Reg is the lower 32-bit temporary which contains the result. -- Use getHiVRegFromLo to find the other VRegUnique. -- diff --git a/compiler/GHC/HsToCore/Expr.hs b/compiler/GHC/HsToCore/Expr.hs index 4fbfbc7d62..ff23a9c168 100644 --- a/compiler/GHC/HsToCore/Expr.hs +++ b/compiler/GHC/HsToCore/Expr.hs @@ -252,8 +252,8 @@ dsLExpr (L loc e) -- | Variant of 'dsLExpr' that ensures that the result is not levity -- polymorphic. This should be used when the resulting expression will -- be an argument to some other function. --- See Note [Levity polymorphism checking] in GHC.HsToCore.Monad --- See Note [Levity polymorphism invariants] in GHC.Core +-- See Note [Levity polymorphism checking] in "GHC.HsToCore.Monad" +-- See Note [Levity polymorphism invariants] in "GHC.Core" dsLExprNoLP :: LHsExpr GhcTc -> DsM CoreExpr dsLExprNoLP (L loc e) = putSrcSpanDs loc $ diff --git a/compiler/GHC/HsToCore/Monad.hs b/compiler/GHC/HsToCore/Monad.hs index 57eaf15cf8..0cd715634a 100644 --- a/compiler/GHC/HsToCore/Monad.hs +++ b/compiler/GHC/HsToCore/Monad.hs @@ -112,7 +112,7 @@ data EquationInfo -- ^ The patterns for an equation -- -- NB: We have /already/ applied 'decideBangHood' to - -- these patterns. See Note [decideBangHood] in GHC.HsToCore.Utils + -- these patterns. See Note [decideBangHood] in "GHC.HsToCore.Utils" , eqn_orig :: Origin -- ^ Was this equation present in the user source? diff --git a/compiler/GHC/HsToCore/PmCheck/Oracle.hs b/compiler/GHC/HsToCore/PmCheck/Oracle.hs index c16a1f1d95..db56ecc98c 100644 --- a/compiler/GHC/HsToCore/PmCheck/Oracle.hs +++ b/compiler/GHC/HsToCore/PmCheck/Oracle.hs @@ -982,7 +982,7 @@ storing required arguments along with the PmAltConLike in 'vi_neg'. -- | Guess the universal argument types of a ConLike from an instantiation of -- its result type. Rather easy for DataCons, but not so much for PatSynCons. --- See Note [Pattern synonym result type] in GHC.Core.PatSyn. +-- See Note [Pattern synonym result type] in "GHC.Core.PatSyn". guessConLikeUnivTyArgsFromResTy :: FamInstEnvs -> Type -> ConLike -> Maybe [Type] guessConLikeUnivTyArgsFromResTy env res_ty (RealDataCon _) = do (tc, tc_args) <- splitTyConApp_maybe res_ty diff --git a/compiler/GHC/HsToCore/PmCheck/Ppr.hs b/compiler/GHC/HsToCore/PmCheck/Ppr.hs index 5845450d21..5b1fe16ba1 100644 --- a/compiler/GHC/HsToCore/PmCheck/Ppr.hs +++ b/compiler/GHC/HsToCore/PmCheck/Ppr.hs @@ -31,7 +31,7 @@ import GHC.HsToCore.PmCheck.Oracle -- | Pretty-print the guts of an uncovered value vector abstraction, i.e., its -- components and refutable shapes associated to any mentioned variables. -- --- Example for @([Just p, q], [p :-> [3,4], q :-> [0,5]]): +-- Example for @([Just p, q], [p :-> [3,4], q :-> [0,5]])@: -- -- @ -- (Just p) q diff --git a/compiler/GHC/HsToCore/Utils.hs b/compiler/GHC/HsToCore/Utils.hs index d29afc5b8d..92b213a951 100644 --- a/compiler/GHC/HsToCore/Utils.hs +++ b/compiler/GHC/HsToCore/Utils.hs @@ -672,7 +672,7 @@ mkSelectorBinds :: [[Tickish Id]] -- ^ ticks to add, possibly -> CoreExpr -- ^ Expression to which the pattern is bound -> DsM (Id,[(Id,CoreExpr)]) -- ^ Id the rhs is bound to, for desugaring strict - -- binds (see Note [Desugar Strict binds] in GHC.HsToCore.Binds) + -- binds (see Note [Desugar Strict binds] in "GHC.HsToCore.Binds") -- and all the desugared binds mkSelectorBinds ticks pat val_expr diff --git a/compiler/GHC/Iface/Ext/Binary.hs b/compiler/GHC/Iface/Ext/Binary.hs index 550b3d0462..2fce4cd2ee 100644 --- a/compiler/GHC/Iface/Ext/Binary.hs +++ b/compiler/GHC/Iface/Ext/Binary.hs @@ -59,7 +59,7 @@ data HieDictionary = HieDictionary initBinMemSize :: Int initBinMemSize = 1024*1024 --- | The header for HIE files - Capital ASCII letters "HIE". +-- | The header for HIE files - Capital ASCII letters \"HIE\". hieMagic :: [Word8] hieMagic = [72,73,69] diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs index 4ba0e1966a..1ce0b1d78f 100644 --- a/compiler/GHC/Iface/Load.hs +++ b/compiler/GHC/Iface/Load.hs @@ -660,12 +660,12 @@ computeInterface doc_str hi_boot_file mod0 = do -- | Compute the signatures which must be compiled in order to -- load the interface for a 'Module'. The output of this function -- is always a subset of 'moduleFreeHoles'; it is more precise --- because in signature @p[A=<A>,B=<B>]:B@, although the free holes +-- because in signature @p[A=\<A>,B=\<B>]:B@, although the free holes -- are A and B, B might not depend on A at all! -- -- If this is invoked on a signature, this does NOT include the -- signature itself; e.g. precise free module holes of --- @p[A=<A>,B=<B>]:B@ never includes B. +-- @p[A=\<A>,B=\<B>]:B@ never includes B. moduleFreeHolesPrecise :: SDoc -> Module -> TcRnIf gbl lcl (MaybeErr MsgDoc (UniqDSet ModuleName)) diff --git a/compiler/GHC/Iface/Recomp/Binary.hs b/compiler/GHC/Iface/Recomp/Binary.hs index c07b5d7d16..8a72a1dcb3 100644 --- a/compiler/GHC/Iface/Recomp/Binary.hs +++ b/compiler/GHC/Iface/Recomp/Binary.hs @@ -1,6 +1,6 @@ {-# LANGUAGE CPP #-} --- | Computing fingerprints of values serializeable with GHC's "Binary" module. +-- | Computing fingerprints of values serializeable with GHC's \"Binary\" module. module GHC.Iface.Recomp.Binary ( -- * Computing fingerprints fingerprintBinMem diff --git a/compiler/GHC/Iface/Rename.hs b/compiler/GHC/Iface/Rename.hs index 50c73e56a9..25f8d19036 100644 --- a/compiler/GHC/Iface/Rename.hs +++ b/compiler/GHC/Iface/Rename.hs @@ -76,18 +76,18 @@ failWithRn doc = do failM -- | What we have is a generalized ModIface, which corresponds to --- a module that looks like p[A=<A>]:B. We need a *specific* ModIface, e.g. --- p[A=q():A]:B (or maybe even p[A=<B>]:B) which we load +-- a module that looks like p[A=\<A>]:B. We need a *specific* ModIface, e.g. +-- p[A=q():A]:B (or maybe even p[A=\<B>]:B) which we load -- up (either to merge it, or to just use during typechecking). -- -- Suppose we have: -- --- p[A=<A>]:M ==> p[A=q():A]:M +-- p[A=\<A>]:M ==> p[A=q():A]:M -- --- Substitute all occurrences of <A> with q():A (renameHoleModule). +-- Substitute all occurrences of \<A> with q():A (renameHoleModule). -- Then, for any Name of form {A.T}, replace the Name with -- the Name according to the exports of the implementing module. --- This works even for p[A=<B>]:M, since we just read in the +-- This works even for p[A=\<B>]:M, since we just read in the -- exports of B.hi, which is assumed to be ready now. -- -- This function takes an optional 'NameShape', which can be used @@ -261,9 +261,9 @@ rnFieldLabel (FieldLabel l b sel) = do -- | The key function. This gets called on every Name embedded -- inside a ModIface. Our job is to take a Name from some --- generalized unit ID p[A=<A>, B=<B>], and change +-- generalized unit ID p[A=\<A>, B=\<B>], and change -- it to the correct name for a (partially) instantiated unit --- ID, e.g. p[A=q[]:A, B=<B>]. +-- ID, e.g. p[A=q[]:A, B=\<B>]. -- -- There are two important things to do: -- @@ -278,12 +278,12 @@ rnFieldLabel (FieldLabel l b sel) = do -- interface precisely to "merge it in". -- -- External case: --- p[A=<B>]:A (and thisUnitId is something else) +-- p[A=\<B>]:A (and thisUnitId is something else) -- We are loading this in order to determine B.hi! So -- don't load B.hi to find the exports. -- -- Local case: --- p[A=<A>]:A (and thisUnitId is p[A=<A>]) +-- p[A=\<A>]:A (and thisUnitId is p[A=\<A>]) -- This should not happen, because the rename is not necessary -- in this case, but if it does we shouldn't load A.hi! -- diff --git a/compiler/GHC/Iface/Syntax.hs b/compiler/GHC/Iface/Syntax.hs index 0e88bce487..5bc777e465 100644 --- a/compiler/GHC/Iface/Syntax.hs +++ b/compiler/GHC/Iface/Syntax.hs @@ -199,7 +199,7 @@ data IfaceFamTyConFlav | IfaceClosedSynFamilyTyCon (Maybe (IfExtName, [IfaceAxBranch])) -- ^ Name of associated axiom and branches for pretty printing purposes, -- or 'Nothing' for an empty closed family without an axiom - -- See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing + -- See Note [Pretty printing via Iface syntax] in "GHC.Core.Ppr.TyThing" | IfaceAbstractClosedSynFamilyTyCon | IfaceBuiltInSynFamTyCon -- for pretty printing purposes only @@ -720,7 +720,7 @@ data ShowHowMuch | ShowSome [OccName] AltPpr -- ^ Show only some sub-components. Specifically, -- - -- [@[]@] Print all sub-components. + -- [@\[\]@] Print all sub-components. -- [@(n:ns)@] Print sub-component @n@ with @ShowSub = ns@; -- elide other sub-components to @...@ -- May 14: the list is max 1 element long at the moment diff --git a/compiler/GHC/Iface/Tidy/StaticPtrTable.hs b/compiler/GHC/Iface/Tidy/StaticPtrTable.hs index 1494db96fc..fe9c77d8a8 100644 --- a/compiler/GHC/Iface/Tidy/StaticPtrTable.hs +++ b/compiler/GHC/Iface/Tidy/StaticPtrTable.hs @@ -3,7 +3,7 @@ -- (c) 2014 I/O Tweag -- -- Each module that uses 'static' keyword declares an initialization function of --- the form hs_spt_init_<module>() which is emitted into the _stub.c file and +-- the form hs_spt_init_\<module>() which is emitted into the _stub.c file and -- annotated with __attribute__((constructor)) so that it gets executed at -- startup time. -- @@ -28,7 +28,7 @@ -- -- The linker must find the definitions matching the @extern StgPtr <name>@ -- declarations. For this to work, the identifiers of static pointers need to be --- exported. This is done in GHC.Core.Opt.SetLevels.newLvlVar. +-- exported. This is done in 'GHC.Core.Opt.SetLevels.newLvlVar'. -- -- There is also a finalization function for the time when the module is -- unloaded. diff --git a/compiler/GHC/Iface/Type.hs b/compiler/GHC/Iface/Type.hs index acd7b51330..75d4911853 100644 --- a/compiler/GHC/Iface/Type.hs +++ b/compiler/GHC/Iface/Type.hs @@ -154,7 +154,7 @@ type IfaceKind = IfaceType -- | A kind of universal type, used for types and kinds. -- -- Any time a 'Type' is pretty-printed, it is first converted to an 'IfaceType' --- before being printed. See Note [Pretty printing via Iface syntax] in GHC.Core.Ppr.TyThing +-- before being printed. See Note [Pretty printing via Iface syntax] in "GHC.Core.Ppr.TyThing" data IfaceType = IfaceFreeTyVar TyVar -- See Note [Free tyvars in IfaceType] | IfaceTyVar IfLclName -- Type/coercion variable only, not tycon diff --git a/compiler/GHC/Llvm.hs b/compiler/GHC/Llvm.hs index 64aba78c3a..f4fde68bdd 100644 --- a/compiler/GHC/Llvm.hs +++ b/compiler/GHC/Llvm.hs @@ -6,7 +6,7 @@ -- LLVM binding library in Haskell, but enough to generate code for GHC. -- -- This code is derived from code taken from the Essential Haskell Compiler --- (EHC) project (<http://www.cs.uu.nl/wiki/Ehc/WebHome>). +-- (EHC) project. -- module GHC.Llvm ( diff --git a/compiler/GHC/Llvm/MetaData.hs b/compiler/GHC/Llvm/MetaData.hs index b485d94dbe..f4adff45bb 100644 --- a/compiler/GHC/Llvm/MetaData.hs +++ b/compiler/GHC/Llvm/MetaData.hs @@ -12,8 +12,8 @@ import GHC.Utils.Outputable -- -- The LLVM metadata feature is poorly documented but roughly follows the -- following design: --- * Metadata can be constructed in a few different ways (See below). --- * After which it can either be attached to LLVM statements to pass along +-- - Metadata can be constructed in a few different ways (See below). +-- - After which it can either be attached to LLVM statements to pass along -- extra information to the optimizer and code generator OR specifically named -- metadata has an affect on the whole module (i.e., linking behaviour). -- @@ -21,18 +21,18 @@ import GHC.Utils.Outputable -- # Constructing metadata -- Metadata comes largely in three forms: -- --- * Metadata expressions -- these are the raw metadata values that encode +-- - Metadata expressions -- these are the raw metadata values that encode -- information. They consist of metadata strings, metadata nodes, regular -- LLVM values (both literals and references to global variables) and -- metadata expressions (i.e., recursive data type). Some examples: -- !{ !"hello", !0, i32 0 } -- !{ !1, !{ i32 0 } } -- --- * Metadata nodes -- global metadata variables that attach a metadata +-- - Metadata nodes -- global metadata variables that attach a metadata -- expression to a number. For example: -- !0 = !{ [<metadata expressions>] !} -- --- * Named metadata -- global metadata variables that attach a metadata nodes +-- - Named metadata -- global metadata variables that attach a metadata nodes -- to a name. Used ONLY to communicated module level information to LLVM -- through a meaningful name. For example: -- !llvm.module.linkage = !{ !0, !1 } @@ -41,7 +41,7 @@ import GHC.Utils.Outputable -- # Using Metadata -- Using metadata depends on the form it is in: -- --- * Attach to instructions -- metadata can be attached to LLVM instructions +-- - Attach to instructions -- metadata can be attached to LLVM instructions -- using a specific reference as follows: -- %l = load i32* @glob, !nontemporal !10 -- %m = load i32* @glob, !nontemporal !{ i32 0, !{ i32 0 } } @@ -49,12 +49,12 @@ import GHC.Utils.Outputable -- Refer to LLVM documentation for which instructions take metadata and its -- meaning. -- --- * As arguments -- llvm functions can take metadata as arguments, for +-- - As arguments -- llvm functions can take metadata as arguments, for -- example: -- call void @llvm.dbg.value(metadata !{ i32 0 }, i64 0, metadata !1) -- As with instructions, only metadata nodes or expressions can be attached. -- --- * As a named metadata -- Here the metadata is simply declared in global +-- - As a named metadata -- Here the metadata is simply declared in global -- scope using a specific name to communicate module level information to LLVM. -- For example: -- !llvm.module.linkage = !{ !0, !1 } @@ -82,8 +82,8 @@ data MetaAnnot = MetaAnnot LMString MetaExpr -- | Metadata declarations. Metadata can only be declared in global scope. data MetaDecl -- | Named metadata. Only used for communicating module information to - -- LLVM. ('!name = !{ [!<n>] }' form). + -- LLVM. ('!name = !{ [!\<n>] }' form). = MetaNamed !LMString [MetaId] -- | Metadata node declaration. - -- ('!0 = metadata !{ <metadata expression> }' form). + -- ('!0 = metadata !{ \<metadata expression> }' form). | MetaUnnamed !MetaId !MetaExpr diff --git a/compiler/GHC/Rename/Unbound.hs b/compiler/GHC/Rename/Unbound.hs index f97d52aac1..ec0084fa4c 100644 --- a/compiler/GHC/Rename/Unbound.hs +++ b/compiler/GHC/Rename/Unbound.hs @@ -93,7 +93,7 @@ type HowInScope = Either SrcSpan ImpDeclSpec -- Right ispec => imported as specified by ispec --- | Called from the typechecker (GHC.Tc.Errors) when we find an unbound variable +-- | Called from the typechecker ("GHC.Tc.Errors") when we find an unbound variable unknownNameSuggestions :: DynFlags -> HomePackageTable -> Module -> GlobalRdrEnv -> LocalRdrEnv -> ImportAvails diff --git a/compiler/GHC/Runtime/Heap/Layout.hs b/compiler/GHC/Runtime/Heap/Layout.hs index 4f32cec7c4..4f43c13344 100644 --- a/compiler/GHC/Runtime/Heap/Layout.hs +++ b/compiler/GHC/Runtime/Heap/Layout.hs @@ -148,7 +148,7 @@ halfWordSizeInBits platform = platformWordSizeInBits platform `div` 2 -} -- | A description of the layout of a closure. Corresponds directly --- to the closure types in includes/rts/storage/ClosureTypes.h. +-- to the closure types in includes\/rts\/storage\/ClosureTypes.h. data SMRep = HeapRep -- GC routines consult sizes in info tbl IsStatic @@ -173,7 +173,7 @@ data SMRep Int -- type tags, so this form lets us override the default SMRep -- tag for an SMRep. --- | True <=> This is a static closure. Affects how we garbage-collect it. +-- | True \<=> This is a static closure. Affects how we garbage-collect it. -- Static closure have an extra static link field at the end. -- Constructors do not have a static variant; see Note [static constructors] type IsStatic = Bool @@ -274,12 +274,12 @@ isStaticNoCafCon _ = False fixedHdrSize :: DynFlags -> ByteOff fixedHdrSize dflags = wordsToBytes (targetPlatform dflags) (fixedHdrSizeW dflags) --- | Size of a closure header (StgHeader in includes/rts/storage/Closures.h) +-- | Size of a closure header (StgHeader in includes\/rts\/storage\/Closures.h) fixedHdrSizeW :: DynFlags -> WordOff fixedHdrSizeW dflags = sTD_HDR_SIZE dflags + profHdrSize dflags -- | Size of the profiling part of a closure header --- (StgProfHeader in includes/rts/storage/Closures.h) +-- (StgProfHeader in includes\/rts\/storage\/Closures.h) profHdrSize :: DynFlags -> WordOff profHdrSize dflags | gopt Opt_SccProfilingOn dflags = pROF_HDR_SIZE dflags diff --git a/compiler/GHC/Runtime/Linker/Types.hs b/compiler/GHC/Runtime/Linker/Types.hs index d4539712e2..429a658042 100644 --- a/compiler/GHC/Runtime/Linker/Types.hs +++ b/compiler/GHC/Runtime/Linker/Types.hs @@ -91,7 +91,7 @@ data Unlinked -- carries some static pointer table entries which -- should be loaded along with the BCOs. -- See Note [Grant plan for static forms] in - -- GHC.Iface.Tidy.StaticPtrTable. + -- "GHC.Iface.Tidy.StaticPtrTable". instance Outputable Unlinked where ppr (DotO path) = text "DotO" <+> text path @@ -100,7 +100,7 @@ instance Outputable Unlinked where ppr (BCOs bcos spt) = text "BCOs" <+> ppr bcos <+> ppr spt -- | An entry to be inserted into a module's static pointer table. --- See Note [Grand plan for static forms] in GHC.Iface.Tidy.StaticPtrTable. +-- See Note [Grand plan for static forms] in "GHC.Iface.Tidy.StaticPtrTable". data SptEntry = SptEntry Id Fingerprint instance Outputable SptEntry where diff --git a/compiler/GHC/StgToCmm/Closure.hs b/compiler/GHC/StgToCmm/Closure.hs index b21277641b..98a9c878af 100644 --- a/compiler/GHC/StgToCmm/Closure.hs +++ b/compiler/GHC/StgToCmm/Closure.hs @@ -144,7 +144,7 @@ nonVoidIds ids = [NonVoid id | id <- ids, not (isVoidTy (idType id))] -- | Used in places where some invariant ensures that all these Ids are -- non-void; e.g. constructor field binders in case expressions. --- See Note [Post-unarisation invariants] in GHC.Stg.Unarise. +-- See Note [Post-unarisation invariants] in "GHC.Stg.Unarise". assertNonVoidIds :: [Id] -> [NonVoid Id] assertNonVoidIds ids = ASSERT(not (any (isVoidTy . idType) ids)) coerce ids @@ -154,7 +154,7 @@ nonVoidStgArgs args = [NonVoid arg | arg <- args, not (isVoidTy (stgArgType arg) -- | Used in places where some invariant ensures that all these arguments are -- non-void; e.g. constructor arguments. --- See Note [Post-unarisation invariants] in GHC.Stg.Unarise. +-- See Note [Post-unarisation invariants] in "GHC.Stg.Unarise". assertNonVoidStgArgs :: [StgArg] -> [NonVoid StgArg] assertNonVoidStgArgs args = ASSERT(not (any (isVoidTy . stgArgType) args)) coerce args diff --git a/compiler/GHC/StgToCmm/Heap.hs b/compiler/GHC/StgToCmm/Heap.hs index 17b57e1f1d..1804193de4 100644 --- a/compiler/GHC/StgToCmm/Heap.hs +++ b/compiler/GHC/StgToCmm/Heap.hs @@ -344,7 +344,7 @@ entryHeapCheck cl_info nodeSet arity args code Just (_, ArgGen _) -> False _otherwise -> True --- | lower-level version for GHC.Cmm.Parser +-- | lower-level version for "GHC.Cmm.Parser" entryHeapCheck' :: Bool -- is a known function pattern -> CmmExpr -- expression for the closure pointer -> Int -- Arity -- not same as len args b/c of voids diff --git a/compiler/GHC/SysTools/Process.hs b/compiler/GHC/SysTools/Process.hs index 4f11a29ea1..d09a3bd09c 100644 --- a/compiler/GHC/SysTools/Process.hs +++ b/compiler/GHC/SysTools/Process.hs @@ -348,8 +348,8 @@ parseError s0 = case breakColon s0 of -- taking care to ignore colons in Windows drive letters (as noted in #17786). -- For instance, -- --- * @"hi.c: ABCD"@ is mapped to @Just ("hi.c", "ABCD")@ --- * @"C:\hi.c: ABCD"@ is mapped to @Just ("C:\hi.c", "ABCD")@ +-- * @"hi.c: ABCD"@ is mapped to @Just ("hi.c", \"ABCD\")@ +-- * @"C:\\hi.c: ABCD"@ is mapped to @Just ("C:\\hi.c", \"ABCD\")@ breakColon :: String -> Maybe (String, String) breakColon = go [] where 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 diff --git a/compiler/GHC/Unit/Info.hs b/compiler/GHC/Unit/Info.hs index b99a9327dc..ee51086e13 100644 --- a/compiler/GHC/Unit/Info.hs +++ b/compiler/GHC/Unit/Info.hs @@ -43,7 +43,7 @@ import GHC.Unit.Ppr -- * UnitId: identifier used to generate code (cf 'UnitInfo') -- -- These two identifiers are different for wired-in packages. See Note [About --- Units] in GHC.Unit +-- Units] in "GHC.Unit" type GenUnitInfo unit = GenericUnitInfo (Indefinite unit) PackageId PackageName unit ModuleName (GenModule (GenUnit unit)) -- | A unit key in the database diff --git a/compiler/GHC/Unit/State.hs b/compiler/GHC/Unit/State.hs index aa1318ad5d..5413990b81 100644 --- a/compiler/GHC/Unit/State.hs +++ b/compiler/GHC/Unit/State.hs @@ -124,11 +124,11 @@ import qualified Data.Set as Set -- The unit state is computed by 'initUnits', and kept in DynFlags. -- It is influenced by various command-line flags: -- --- * @-package <pkg>@ and @-package-id <pkg>@ cause @<pkg>@ to become exposed. +-- * @-package \<pkg>@ and @-package-id \<pkg>@ cause @\<pkg>@ to become exposed. -- If @-hide-all-packages@ was not specified, these commands also cause -- all other packages with the same name to become hidden. -- --- * @-hide-package <pkg>@ causes @<pkg>@ to become hidden. +-- * @-hide-package \<pkg>@ causes @\<pkg>@ to become hidden. -- -- * (there are a few more flags, check below for their semantics) -- @@ -431,9 +431,9 @@ data UnitState = UnitState { -- | A map saying, for each requirement, what interfaces must be merged -- together when we use them. For example, if our dependencies - -- are @p[A=<A>]@ and @q[A=<A>,B=r[C=<A>]:B]@, then the interfaces - -- to merge for A are @p[A=<A>]:A@, @q[A=<A>,B=r[C=<A>]:B]:A@ - -- and @r[C=<A>]:C@. + -- are @p[A=\<A>]@ and @q[A=\<A>,B=r[C=\<A>]:B]@, then the interfaces + -- to merge for A are @p[A=\<A>]:A@, @q[A=\<A>,B=r[C=\<A>]:B]:A@ + -- and @r[C=\<A>]:C@. -- -- There's an entry in this map for each hole in our home library. requirementContext :: Map ModuleName [InstantiatedModule], @@ -2215,20 +2215,20 @@ type ShHoleSubst = ModuleNameEnv Module -- | Substitutes holes in a 'Module'. NOT suitable for being called -- directly on a 'nameModule', see Note [Representation of module/name variable]. --- @p[A=<A>]:B@ maps to @p[A=q():A]:B@ with @A=q():A@; --- similarly, @<A>@ maps to @q():A@. +-- @p[A=\<A>]:B@ maps to @p[A=q():A]:B@ with @A=q():A@; +-- similarly, @\<A>@ maps to @q():A@. renameHoleModule :: UnitState -> ShHoleSubst -> Module -> Module renameHoleModule state = renameHoleModule' (unitInfoMap state) (preloadClosure state) -- | Substitutes holes in a 'Unit', suitable for renaming when -- an include occurs; see Note [Representation of module/name variable]. -- --- @p[A=<A>]@ maps to @p[A=<B>]@ with @A=<B>@. +-- @p[A=\<A>]@ maps to @p[A=\<B>]@ with @A=\<B>@. renameHoleUnit :: UnitState -> ShHoleSubst -> Unit -> Unit renameHoleUnit state = renameHoleUnit' (unitInfoMap state) (preloadClosure state) -- | Like 'renameHoleModule', but requires only 'ClosureUnitInfoMap' --- so it can be used by "Packages". +-- so it can be used by "GHC.Unit.State". renameHoleModule' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Module -> Module renameHoleModule' pkg_map closure env m | not (isHoleModule m) = @@ -2239,7 +2239,7 @@ renameHoleModule' pkg_map closure env m | otherwise = m -- | Like 'renameHoleUnit, but requires only 'ClosureUnitInfoMap' --- so it can be used by "Packages". +-- so it can be used by "GHC.Unit.State". renameHoleUnit' :: UnitInfoMap -> PreloadUnitClosure -> ShHoleSubst -> Unit -> Unit renameHoleUnit' pkg_map closure env uid = case uid of diff --git a/compiler/GHC/Utils/Asm.hs b/compiler/GHC/Utils/Asm.hs index 5b8b209f5e..2841ad3efa 100644 --- a/compiler/GHC/Utils/Asm.hs +++ b/compiler/GHC/Utils/Asm.hs @@ -1,7 +1,7 @@ -- | Various utilities used in generating assembler. -- -- These are used not only by the native code generator, but also by the --- GHC.Driver.Pipeline +-- "GHC.Driver.Pipeline" module GHC.Utils.Asm ( sectionType ) where diff --git a/compiler/GHC/Utils/Binary.hs b/compiler/GHC/Utils/Binary.hs index 10810ba96a..d95041665a 100644 --- a/compiler/GHC/Utils/Binary.hs +++ b/compiler/GHC/Utils/Binary.hs @@ -1089,7 +1089,7 @@ lazyGet bh = do -- These two settings have different needs while serializing Names: -- -- * Names in interface files are serialized via a symbol table (see Note --- [Symbol table representation of names] in GHC.Iface.Binary). +-- [Symbol table representation of names] in "GHC.Iface.Binary"). -- -- * During fingerprinting a binding Name is serialized as the OccName and a -- non-binding Name is serialized as the fingerprint of the thing they diff --git a/compiler/GHC/Utils/Error.hs b/compiler/GHC/Utils/Error.hs index 3bb9aa7329..4c72c052d7 100644 --- a/compiler/GHC/Utils/Error.hs +++ b/compiler/GHC/Utils/Error.hs @@ -170,16 +170,16 @@ data Severity | SevDump -- ^ Log message intended for compiler developers - -- No file/line/column stuff + -- No file\/line\/column stuff | SevInfo -- ^ Log messages intended for end users. - -- No file/line/column stuff. + -- No file\/line\/column stuff. | SevWarning | SevError -- ^ SevWarning and SevError are used for warnings and errors - -- o The message has a file/line/column heading, + -- o The message has a file\/line\/column heading, -- plus "warning:" or "error:", -- added by mkLocMessags -- o Output is intended for end users diff --git a/compiler/GHC/Utils/Outputable.hs b/compiler/GHC/Utils/Outputable.hs index 151800a30b..b3d1772076 100644 --- a/compiler/GHC/Utils/Outputable.hs +++ b/compiler/GHC/Utils/Outputable.hs @@ -958,7 +958,7 @@ instance Outputable Extension where -- | 'BindingSite' is used to tell the thing that prints binder what -- language construct is binding the identifier. This can be used -- to decide how much info to print. --- Also see Note [Binding-site specific printing] in GHC.Core.Ppr +-- Also see Note [Binding-site specific printing] in "GHC.Core.Ppr" data BindingSite = LambdaBind -- ^ The x in (\x. e) | CaseBind -- ^ The x in case scrut of x { (y,z) -> ... } diff --git a/compiler/GHC/Utils/Panic.hs b/compiler/GHC/Utils/Panic.hs index 9d960644b6..551e9337de 100644 --- a/compiler/GHC/Utils/Panic.hs +++ b/compiler/GHC/Utils/Panic.hs @@ -56,12 +56,12 @@ import System.Mem.Weak ( deRefWeak ) -- error messages all take the form: -- -- @ --- <location>: <error> +-- \<location>: \<error> -- @ -- -- If the location is on the command line, or in GHC itself, then --- <location>="ghc". All of the error types below correspond to --- a <location> of "ghc", except for ProgramError (where the string is +-- \<location>="ghc". All of the error types below correspond to +-- a \<location> of "ghc", except for ProgramError (where the string is -- assumed to contain a location already, so we don't print one). data GhcException @@ -128,7 +128,7 @@ safeShowException e = do -- | Append a description of the given exception to this string. -- --- Note that this uses 'DynFlags.unsafeGlobalDynFlags', which may have some +-- Note that this uses 'GHC.Driver.Session.unsafeGlobalDynFlags', which may have some -- uninitialized fields if invoked before 'GHC.initGhcMonad' has been called. -- If the error message to be printed includes a pretty-printer document -- which forces one of these fields this call may bottom. diff --git a/compiler/GHC/Utils/Panic/Plain.hs b/compiler/GHC/Utils/Panic/Plain.hs index 8e4aed5046..8e54f81cde 100644 --- a/compiler/GHC/Utils/Panic/Plain.hs +++ b/compiler/GHC/Utils/Panic/Plain.hs @@ -1,13 +1,13 @@ {-# LANGUAGE CPP, ScopedTypeVariables, LambdaCase #-} -- | Defines a simple exception type and utilities to throw it. The --- 'PlainGhcException' type is a subset of the 'Panic.GhcException' +-- 'PlainGhcException' type is a subset of the 'GHC.Utils.Panic.GhcException' -- type. It omits the exception constructors that involve --- pretty-printing via 'Outputable.SDoc'. +-- pretty-printing via 'GHC.Utils.Outputable.SDoc'. -- -- There are two reasons for this: -- --- 1. To avoid import cycles / use of boot files. "Outputable" has +-- 1. To avoid import cycles / use of boot files. "GHC.Utils.Outputable" has -- many transitive dependencies. To throw exceptions from these -- modules, the functions here can be used without introducing import -- cycles. @@ -34,14 +34,14 @@ import GHC.Prelude import System.Environment import System.IO.Unsafe --- | This type is very similar to 'Panic.GhcException', but it omits +-- | This type is very similar to 'GHC.Utils.Panic.GhcException', but it omits -- the constructors that involve pretty-printing via --- 'Outputable.SDoc'. Due to the implementation of 'fromException' --- for 'Panic.GhcException', this type can be caught as a --- 'Panic.GhcException'. +-- 'GHC.Utils.Outputable.SDoc'. Due to the implementation of 'fromException' +-- for 'GHC.Utils.Panic.GhcException', this type can be caught as a +-- 'GHC.Utils.Panic.GhcException'. -- -- Note that this should only be used for throwing exceptions, not for --- catching, as 'Panic.GhcException' will not be converted to this +-- catching, as 'GHC.Utils.Panic.GhcException' will not be converted to this -- type when catching. data PlainGhcException -- | Some other fatal signal (SIGHUP,SIGTERM) diff --git a/compiler/GHC/Utils/Ppr.hs b/compiler/GHC/Utils/Ppr.hs index 96e1328ff7..3fa84850b8 100644 --- a/compiler/GHC/Utils/Ppr.hs +++ b/compiler/GHC/Utils/Ppr.hs @@ -16,7 +16,7 @@ -- Based on /The Design of a Pretty-printing Library/ -- in Advanced Functional Programming, -- Johan Jeuring and Erik Meijer (eds), LNCS 925 --- <http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps> +-- <http://www.cse.chalmers.se/~rjmh/Papers/pretty.ps> -- ----------------------------------------------------------------------------- |