diff options
author | Ben Gamari <ben@smart-cactus.org> | 2022-01-30 08:16:32 -0500 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2022-02-08 05:28:42 -0500 |
commit | 457a5b9c6eadfd13548f25c5568d5c802d22f411 (patch) | |
tree | e3586ecc534fe931f94123ee405d1ad4a9edf9ac /utils | |
parent | a893d2f383212271644401c7088cf937eb453fa3 (diff) | |
download | haskell-457a5b9c6eadfd13548f25c5568d5c802d22f411.tar.gz |
notes-util: initial commit
Diffstat (limited to 'utils')
-rw-r--r-- | utils/notes-util/Main.hs | 54 | ||||
-rw-r--r-- | utils/notes-util/Notes.hs | 163 | ||||
-rwxr-xr-x | utils/notes-util/check.sh | 29 | ||||
-rw-r--r-- | utils/notes-util/expected-broken-note-refs | 853 | ||||
-rw-r--r-- | utils/notes-util/notes-util.cabal | 20 | ||||
-rw-r--r-- | utils/notes-util/test | 25 |
6 files changed, 1144 insertions, 0 deletions
diff --git a/utils/notes-util/Main.hs b/utils/notes-util/Main.hs new file mode 100644 index 0000000000..d685001d1c --- /dev/null +++ b/utils/notes-util/Main.hs @@ -0,0 +1,54 @@ +import qualified Data.Set as S +import System.Process +import System.Environment + +import Notes + +usage :: IO a +usage = do + putStrLn $ unlines + [ "usage:" + , " ghc-notes <mode>" + , " ghc-notes <mode> @<response-file>" + , " ghc-notes <mode> <file>" + , "" + , "valid modes:" + , " dump dump all Note definitions and references" + , " defs dump all Note definitions" + , " refs dump all Note references" + , " unreferenced dump all unreferenced Note definitions" + , " broken-refs dump all references to missing Notes" + ] + fail "invalid usage" + +main :: IO () +main = do + args <- getArgs + + let printNoteDefs = putStrLn . unlines . map showNoteDef + printNoteRefs = putStrLn . unlines . map showNoteRef + + parseMode :: String -> Maybe (NoteDb -> IO ()) + parseMode "dump" = Just $ putStrLn . showNoteDb + parseMode "unreferenced" = Just $ printNoteDefs . S.toList . unreferencedNotes + parseMode "defs" = Just $ printNoteDefs . allNoteDefs + parseMode "refs" = Just $ printNoteRefs . allNoteRefs + parseMode "broken-refs" = Just $ printNoteRefs . brokenNoteRefs + parseMode _ = Nothing + + (mode, files) <- case args of + [mode, "@-"] -> do + files <- lines <$> getContents + return (parseMode mode, files) + [mode, '@':respFile] -> do + files <- lines <$> readFile respFile + return (parseMode mode, files) + [mode] -> do + files <- lines <$> readProcess "git" ["ls-tree", "--name-only", "-r", "HEAD"] "" + return (parseMode mode, files) + _ -> usage + + case mode of + Just run -> filesNotes files >>= run + Nothing -> return () + diff --git a/utils/notes-util/Notes.hs b/utils/notes-util/Notes.hs new file mode 100644 index 0000000000..f27b483536 --- /dev/null +++ b/utils/notes-util/Notes.hs @@ -0,0 +1,163 @@ +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE BangPatterns #-} + +module Notes where + +import Data.Either +import Data.Foldable +import qualified Data.ByteString as BS +import qualified Data.Text as T +import qualified Data.Text.Encoding as T +import qualified Data.Map.Strict as M +import qualified Data.Set as S +import System.Directory (doesFileExist) + +data SrcLoc = SrcLoc { fileName :: FilePath + , row :: !Int + , column :: !Int + } + deriving (Eq, Ord, Show) + +showSrcLoc :: SrcLoc -> String +showSrcLoc loc = + concat [fileName loc, ":", show (row loc), ":", show (column loc), ":"] + +newtype NoteName = NoteName T.Text + deriving (Eq, Ord, Show) + +showNoteName :: NoteName -> String +showNoteName (NoteName x) = "Note [" <> T.unpack x <> "]" + +data NoteDef = NoteDef { noteDefSrcLoc :: !SrcLoc + , noteDefName :: !NoteName + } + deriving (Eq, Ord, Show) + +showNoteDef :: NoteDef -> String +showNoteDef (NoteDef{noteDefSrcLoc=loc, noteDefName=name}) = + "def " <> showSrcLoc loc <> " " <> showNoteName name + +data NoteRef = NoteRef { noteRefSrcLoc :: !SrcLoc + , noteRefName :: !NoteName + } + deriving (Eq, Ord, Show) + +showNoteRef :: NoteRef -> String +showNoteRef (NoteRef{noteRefSrcLoc=loc, noteRefName=name}) = + "ref " <> showSrcLoc loc <> " " <> showNoteName name + +findNotes :: FilePath -> T.Text -> [Either NoteRef NoteDef] +findNotes fname t = + go 1 (T.lines t) + where + go :: Int -> [T.Text] -> [Either NoteRef NoteDef] + -- Note definitions: + -- We look for a "Note [" token with a "~~~" rule beneath it. + go !lineNo (l0 : l1 : ls) + | hasRule = Right (NoteDef srcLoc name) : go (lineNo+2) ls + where + (prefix, rest) = T.breakOn "Note [" l0 + startCol = T.length prefix + hasRule = T.take 3 (T.drop startCol l1) == "~~~" + srcLoc = SrcLoc fname lineNo startCol + name = NoteName $ T.takeWhile (/= ']') $ T.drop 6 rest + + -- Note references: + -- We look for a "Note [...]", strip away any beginning-of-line + -- comment symbols, and merge whitespace. + go lineNo (l0 : ls) = + [ Left (NoteRef srcLoc (NoteName name)) + | (prefix, rest) <- T.breakOnAll "Note [" l0 + , let startCol = T.length prefix + srcLoc = SrcLoc fname lineNo startCol + (name, suffix) = T.breakOn "]" (T.drop 6 rest<>" "<>T.concat (map stripBeginningOfLineComment $ take 1 ls)) + , "]" `T.isPrefixOf` suffix + ] ++ go (lineNo+1) ls + + go _lineNo [] = [] + +stripBeginningOfLineComment :: T.Text -> T.Text +stripBeginningOfLineComment = T.pack . go . T.unpack + where + -- This implements the following regular expression substitution: + -- + -- s/$ *[(\-\- )\#( \* )] */ / + + go :: String -> String + go ('#':rest) = finish rest + go ('-':'-':rest) = finish rest + go (' ':'*':rest) = finish rest + go ('/':'/':rest) = finish rest + go (' ':rest) = go rest + go xs = finish xs + + finish :: String -> String + finish = dropWhile (==' ') + +data NoteDb = NoteDb { noteRefs :: M.Map FilePath (S.Set NoteRef) + , noteDefs :: M.Map NoteName (S.Set NoteDef) + } + +instance Monoid NoteDb where + mempty = NoteDb M.empty M.empty + +instance Semigroup NoteDb where + NoteDb a b <> NoteDb c d = + NoteDb (M.unionWith (<>) a c) (M.unionWith (<>) b d) + +allNoteDefs :: NoteDb -> [NoteDef] +allNoteDefs db = + [ def + | defs <- M.elems (noteDefs db) + , def <- S.toList defs + ] + +allNoteRefs :: NoteDb -> [NoteRef] +allNoteRefs db = + [ ref + | (_fname, refs) <- M.toList (noteRefs db) + , ref <- S.toList refs + ] + +showNoteDb :: NoteDb -> String +showNoteDb db = unlines $ + map showNoteRef (allNoteRefs db) + ++ + map showNoteDef (allNoteDefs db) + +filesNotes :: [FilePath] + -> IO NoteDb +filesNotes = fmap mconcat . mapM fileNotes + +fileNotes :: FilePath -> IO NoteDb +fileNotes fname = do + is_file <- doesFileExist fname + if is_file + then do + bs <- BS.readFile fname + return $ case T.decodeUtf8' bs of + Left _ -> mempty + Right t -> + let (refs, defs) = partitionEithers (findNotes fname t) + in NoteDb + { noteRefs = M.singleton fname (S.fromList refs) + , noteDefs = M.fromList + [ (noteDefName def, S.singleton def) + | def <- defs + ] + } + else return mempty + +brokenNoteRefs :: NoteDb -> [NoteRef] +brokenNoteRefs db = + [ ref + | (_fname, refs) <- M.toList (noteRefs db) + , ref <- S.toList refs + , Nothing <- pure $ M.lookup (noteRefName ref) (noteDefs db) + ] + +unreferencedNotes :: NoteDb -> S.Set NoteDef +unreferencedNotes db = + fold $ noteDefs db `M.withoutKeys` referencedNotes + where + referencedNotes = S.fromList $ map noteRefName (allNoteRefs db) diff --git a/utils/notes-util/check.sh b/utils/notes-util/check.sh new file mode 100755 index 0000000000..079eeec1cd --- /dev/null +++ b/utils/notes-util/check.sh @@ -0,0 +1,29 @@ +#!/bin/sh + +set -e + +CABAL_INSTALL="${CABAL_INSTALL:-cabal}" + +cd "$(dirname $0)" +"$CABAL_INSTALL" build +bin="$("$CABAL_INSTALL" list-bin ghc-notes)" +cd "$(git rev-parse --show-toplevel)" +"$bin" broken-refs \ + | grep -v "utils/notes-util/expected-broken-note-refs:" \ + | sed 's/:[0-9]\+:[0-9]\+:/:/' \ + > broken-note-refs + +if diff -q utils/notes-util/expected-broken-note-refs broken-note-refs; then + printf "No unexpected broken note references" +else + printf "Found unexpected broken note references:\n\n" + diff -u utils/notes-util/expected-broken-note-refs broken-note-refs || true + if [[ "$1" == "-a" ]]; then + cp broken-note-refs utils/notes-util/expected-broken-note-refs + printf "\n" + printf "Accepted new broken note references." + else + exit 1 + fi +fi + diff --git a/utils/notes-util/expected-broken-note-refs b/utils/notes-util/expected-broken-note-refs new file mode 100644 index 0000000000..c0c291f06b --- /dev/null +++ b/utils/notes-util/expected-broken-note-refs @@ -0,0 +1,853 @@ +ref .mailmap: Note [usrbincc] +ref .mailmap: Note [geoffw] +ref .mailmap: Note [zhuang] +ref .mailmap: Note [uid245] +ref .mailmap: Note [geoffw] +ref .mailmap: Note [uid245] +ref .mailmap: Note [usrbincc] +ref .mailmap: Note [zhuang] +ref Makefile: Note [install-strip] +ref Makefile: Note [install-strip] +ref Makefile: Note [install-strip] +ref Makefile: Note [validate and testsuite speed] +ref bindisttest/install: Note [Spaces in TEST_HC] +ref compiler/CodeGen.Platform.h: Note [esi/edi/ebp not allocatable] +ref compiler/CodeGen.Platform.h: Note [esi/edi/ebp not allocatable] +ref compiler/GHC/Builtin/Names.hs: Note [TyConRepNames for non-wired-in TyCons] +ref compiler/GHC/ByteCode/Asm.hs: Note [GHCi tuple layout] +ref compiler/GHC/ByteCode/Types.hs: Note [Syncing breakpoint info] +ref compiler/GHC/Cmm/CLabel.hs: Note [Proc-point local block entry-point] +ref compiler/GHC/Cmm/CLabel.hs: Note [Proc-point local block entry-point] +ref compiler/GHC/Cmm/CLabel.hs: Note [Proc-point local block entry-point] +ref compiler/GHC/Cmm/CLabel.hs: Note [.LCTOC1 in PPC PIC code] +ref compiler/GHC/Cmm/Dataflow.hs: Note [Backward vs forward analysis] +ref compiler/GHC/Cmm/Dataflow.hs: Note [Backward vs forward analysis] +ref compiler/GHC/Cmm/Dataflow.hs: Note [No old fact] +ref compiler/GHC/Cmm/Dataflow.hs: Note [No old fact] +ref compiler/GHC/Cmm/DebugBlock.hs: Note [Splitting DebugBlocks] +ref compiler/GHC/Cmm/Expr.hs: Note [Continuation BlockId] +ref compiler/GHC/Cmm/Expr.hs: Note [Continuation BlockId] +ref compiler/GHC/Cmm/Expr.hs: Note [Overlapping global registers] +ref compiler/GHC/Cmm/Expr.hs: Note [GHCi tuple layout] +ref compiler/GHC/Cmm/Graph.hs: Note [Width of parameters] +ref compiler/GHC/Cmm/Graph.hs: Note [Width of parameters] +ref compiler/GHC/Cmm/Graph.hs: Note [Width of parameters] +ref compiler/GHC/Cmm/Graph.hs: Note [Width of parameters] +ref compiler/GHC/Cmm/Info/Build.hs: Note [STATIC_LINK fields] +ref compiler/GHC/Cmm/Info/Build.hs: Note [STATIC_LINK fields] +ref compiler/GHC/Cmm/Info/Build.hs: Note [recursive SRTs] +ref compiler/GHC/Cmm/Info/Build.hs: Note [recursive SRTs] +ref compiler/GHC/Cmm/Info/Build.hs: Note [recursive SRTs] +ref compiler/GHC/Cmm/Info/Build.hs: Note [recursive SRTs] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [Stack Layout] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [Two pass approach] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [Two pass approach] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [diamond proc point] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [diamond proc point] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [SP old/young offsets] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [SP old/young offsets] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [Lower safe foreign calls] +ref compiler/GHC/Cmm/LayoutStack.hs: Note [safe foreign call convention] +ref compiler/GHC/Cmm/Node.hs: Note [CmmTick scoping details] +ref compiler/GHC/Cmm/Node.hs: Note [Continuation BlockIds] +ref compiler/GHC/Cmm/Node.hs: Note [CmmTick scoping details] +ref compiler/GHC/Cmm/Parser.y: Note [Syntax of .cmm files] +ref compiler/GHC/Cmm/Pipeline.hs: Note [unreachable blocks] +ref compiler/GHC/Cmm/Pipeline.hs: Note [inconsistent-pic-reg] +ref compiler/GHC/Cmm/Pipeline.hs: Note [unreachable blocks] +ref compiler/GHC/Cmm/ProcPoint.hs: Note [No simple dataflow] +ref compiler/GHC/Cmm/ProcPoint.hs: Note [Continuation BlockIds] +ref compiler/GHC/Cmm/ProcPoint.hs: Note [Direct reachability] +ref compiler/GHC/Cmm/ProcPoint.hs: Note [No simple dataflow] +ref compiler/GHC/Cmm/Sink.hs: Note [Keeping assignemnts mentioned in skipped RHSs] +ref compiler/GHC/Cmm/Sink.hs: Note [Keeping assignemnts mentioned in skipped RHSs] +ref compiler/GHC/Cmm/Sink.hs: Note [improveConditional] +ref compiler/GHC/Cmm/Sink.hs: Note [Lower safe foreign calls] +ref compiler/GHC/Cmm/Utils.hs: Note [Overlapping global registers] +ref compiler/GHC/CmmToAsm/AArch64/CodeGen.hs: Note [General layout of an NCG] +ref compiler/GHC/CmmToAsm/AArch64/CodeGen.hs: Note [CSET] +ref compiler/GHC/CmmToAsm/AArch64/CodeGen.hs: Note [CSET] +ref compiler/GHC/CmmToAsm/AArch64/Ppr.hs: Note [Subsections Via Symbols] +ref compiler/GHC/CmmToAsm/AArch64/Ppr.hs: Note [Always use objects for info tables] +ref compiler/GHC/CmmToAsm/CFG.hs: Note [Inverting Conditional Branches] +ref compiler/GHC/CmmToAsm/CFG.hs: Note [Updating the CFG during shortcutting] +ref compiler/GHC/CmmToAsm/Dwarf.hs: Note [Splitting DebugBlocks] +ref compiler/GHC/CmmToAsm/Dwarf.hs: Note [Splitting DebugBlocks] +ref compiler/GHC/CmmToAsm/Dwarf/Types.hs: Note [Info offset] +ref compiler/GHC/CmmToAsm/PIC.hs: Note [.LCTOC1 in PPC PIC code] +ref compiler/GHC/CmmToAsm/PIC.hs: Note [.LCTOC1 in PPC PIC code] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [Power instruction format] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [Power instruction format] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [Seemingly useless cmp and bne] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [Seemingly useless cmp and bne] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [implicit register in PPC PIC code] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [.LCTOC1 in PPC PIC code] +ref compiler/GHC/CmmToAsm/PPC/CodeGen.hs: Note [implicit register in PPC PIC code] +ref compiler/GHC/CmmToAsm/PPC/Ppr.hs: Note [Subsections Via Symbols] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [SSE Parity Checks] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [DIV/IDIV for bytes] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [SSE Parity Checks] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [SSE Parity Checks] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [DIV/IDIV for bytes] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [DIV/IDIV for bytes] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [rts/StgCRun.c : Stack Alignment on X86] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [rts/StgCRun.c : Stack Alignment on X86] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [SSE Parity Checks] +ref compiler/GHC/CmmToAsm/X86/CodeGen.hs: Note [SSE Parity Checks] +ref compiler/GHC/CmmToAsm/X86/Instr.hs: Note [x86 Floating point precision] +ref compiler/GHC/CmmToAsm/X86/Instr.hs: Note [Windows stack layout] +ref compiler/GHC/CmmToAsm/X86/Instr.hs: Note [Windows stack allocations] +ref compiler/GHC/CmmToAsm/X86/Instr.hs: Note [Windows stack layout] +ref compiler/GHC/CmmToAsm/X86/Instr.hs: Note [extra spill slots] +ref compiler/GHC/CmmToAsm/X86/Ppr.hs: Note [Subsections Via Symbols] +ref compiler/GHC/CmmToAsm/X86/Ppr.hs: Note [Subsections Via Symbols] +ref compiler/GHC/CmmToC.hs: Note [StgWord alignment] +ref compiler/GHC/CmmToC.hs: Note [StgWord alignment] +ref compiler/GHC/CmmToC.hs: Note [Zero-extended sub-word signed results] +ref compiler/GHC/CmmToLlvm/Base.hs: Note [Llvm Forward References] +ref compiler/GHC/CmmToLlvm/Config.hs: Note [LLVM Configuration] +ref compiler/GHC/Core.hs: Note [Extra args in rule matching] +ref compiler/GHC/Core/Coercion.hs: Note [Unused coercion variable in ForAllCo] +ref compiler/GHC/Core/Coercion.hs: Note [Unused coercion variable in ForAllCo] +ref compiler/GHC/Core/Coercion.hs: Note [Unused coercion variable in ForAllCo] +ref compiler/GHC/Core/Coercion.hs: Note [liftCoSubstVarBndr] +ref compiler/GHC/Core/Coercion.hs: Note [liftCoSubstVarBndr] +ref compiler/GHC/Core/Coercion/Axiom.hs: Note [Compatibility checking] +ref compiler/GHC/Core/Lint.hs: Note [Checking representation-polymorphic data constructors] +ref compiler/GHC/Core/Lint.hs: Note [Unused coercion variable in ForAllCo] +ref compiler/GHC/Core/Lint.hs: Note [Rules and join points] +ref compiler/GHC/Core/Lint.hs: Note [Unused coercion variable in ForAllCo] +ref compiler/GHC/Core/Make.hs: Note [Worker/wrapper for INLINEABLE functions] +ref compiler/GHC/Core/Opt/Arity.hs: Note [Expanding newtypes] +ref compiler/GHC/Core/Opt/Arity.hs: Note [Exciting arity] +ref compiler/GHC/Core/Opt/Arity.hs: Note [Dealing with bottom (1)] +ref compiler/GHC/Core/Opt/Arity.hs: Note [Dealing with bottom (2)] +ref compiler/GHC/Core/Opt/Arity.hs: Note [Check for reflexive casts in eta-expansion] +ref compiler/GHC/Core/Opt/Arity.hs: Note [The EtaInfo mechansim] +ref compiler/GHC/Core/Opt/CSE.hs: Note [Type-let] +ref compiler/GHC/Core/Opt/CallArity.hs: Note [Analysis I: The arity analysis] +ref compiler/GHC/Core/Opt/CallArity.hs: Note [Analysis II: The Co-Called analysis] +ref compiler/GHC/Core/Opt/CallArity.hs: Note [Analysing top-level-binds] +ref compiler/GHC/Core/Opt/CallArity.hs: Note [Analysis II: The Co-Called analysis] +ref compiler/GHC/Core/Opt/CallArity.hs: Note [Analysis I: The arity analysis] +ref compiler/GHC/Core/Opt/CallArity.hs: Note [Analysis II: The Co-Called analysis] +ref compiler/GHC/Core/Opt/ConstantFold.hs: Note [negative zero] +ref compiler/GHC/Core/Opt/ConstantFold.hs: Note [negative zero] +ref compiler/GHC/Core/Opt/ConstantFold.hs: Note [negative zero] +ref compiler/GHC/Core/Opt/ConstantFold.hs: Note [dataToTag#] +ref compiler/GHC/Core/Opt/ConstantFold.hs: Note [dataToTag#] +ref compiler/GHC/Core/Opt/FloatIn.hs: Note [extra_fvs (1,2)] +ref compiler/GHC/Core/Opt/FloatIn.hs: Note [extra_fvs (1,2)] +ref compiler/GHC/Core/Opt/LiberateCase.hs: Note [Not bottoming ids] +ref compiler/GHC/Core/Opt/OccurAnal.hs: Note [Rules for imported functions] +ref compiler/GHC/Core/Opt/OccurAnal.hs: Note [Self-recursive rules] +ref compiler/GHC/Core/Opt/OccurAnal.hs: Note [Rules and loop breakers] +ref compiler/GHC/Core/Opt/OccurAnal.hs: Note [Loop breaking] +ref compiler/GHC/Core/Opt/OccurAnal.hs: Note [Eta-expansion inside stable unfoldings] +ref compiler/GHC/Core/Opt/Pipeline.hs: Note [Simplifying the left-hand side of a RULE] +ref compiler/GHC/Core/Opt/Pipeline.hs: Note [Rules and indirect-zapping] +ref compiler/GHC/Core/Opt/Pipeline.hs: Note [Messing up the exported Id's IdInfo] +ref compiler/GHC/Core/Opt/Pipeline.hs: Note [Messing up the exported Id's IdInfo] +ref compiler/GHC/Core/Opt/SetLevels.hs: Note [Top level scope] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [Wrapper NoUserInline] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [case-of-scc-of-case] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [case-of-scc-of-case] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [case-of-scc-of-case] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [zapSubstEnv] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [RULEs apply to simplified arguments] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [zapSubstEnv] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [Case binder next] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [Suppressing binder-swaps on linear case] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [Lambda-bound unfoldings] +ref compiler/GHC/Core/Opt/Simplify.hs: Note [Do not eta-expand trivial expressions] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [The hole type in ApplyToTy/Val] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [The hole type in ApplyToTy/Val] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [RHS of lets] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [The hole type in ApplyToTy/Val] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [Gentle mode] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [Simplfying rules] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [Eta-expanding lambdas] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [Nerge nested cases] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [Eliminate identity case] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs: Note [Scrutinee constant folding] +ref compiler/GHC/Core/Opt/SpecConstr.hs: Note [ScrutOcc] +ref compiler/GHC/Core/Opt/Specialise.hs: Note [Missed specialization for ClassOps] +ref compiler/GHC/Core/Opt/Specialise.hs: Note [Inline specialisation] +ref compiler/GHC/Core/Opt/Specialise.hs: Note [Arity decrease] +ref compiler/GHC/Core/Opt/WorkWrap.hs: Note [Demand on the Worker] +ref compiler/GHC/Core/Opt/WorkWrap.hs: Note [Wrapper NoUserInline] +ref compiler/GHC/Core/Opt/WorkWrap.hs: Note [About the NameSorts] +ref compiler/GHC/Core/Opt/WorkWrap.hs: Note [About the NameSorts] +ref compiler/GHC/Core/Opt/WorkWrap/Utils.hs: Note [Boxity Analysis] +ref compiler/GHC/Core/Rules.hs: Note [Coercion argument] +ref compiler/GHC/Core/Rules.hs: Note [Eta reduction in the target] +ref compiler/GHC/Core/Rules.hs: Note [Eta reduction in the target] +ref compiler/GHC/Core/Subst.hs: Note [Apply once] +ref compiler/GHC/Core/Subst.hs: Note [Extending the TCvSubst] +ref compiler/GHC/Core/TyCo/FVs.hs: Note [Free variables of Coercions] +ref compiler/GHC/Core/TyCo/FVs.hs: Note [Unused coercion variable in ForAllCo] +ref compiler/GHC/Core/TyCo/Ppr.hs: Note [IfaceType and pretty-printing] +ref compiler/GHC/Core/TyCo/Rep.hs: Note [What prevents a constraint from floating] +ref compiler/GHC/Core/TyCo/Subst.hs: Note [Extending the TCvSubst] +ref compiler/GHC/Core/TyCo/Subst.hs: Note [Extending the TCvSubst] +ref compiler/GHC/Core/TyCon.hs: Note [Promoted GADT data construtors] +ref compiler/GHC/Core/TyCon.hs: Note [Promoted GADT data construtors] +ref compiler/GHC/Core/TyCon.hs: Note [bad unsafe coercion] +ref compiler/GHC/Core/TyCon.hs: Note [The Purely Kinded Invariant] +ref compiler/GHC/Core/TyCon.hs: Note [Sharing nullary TyCons] +ref compiler/GHC/Core/Unfold.hs: Note [RHS of lets] +ref compiler/GHC/Core/Unfold.hs: Note [INLINE for small functions (3)] +ref compiler/GHC/Core/Unfold.hs: Note [Unfold info lazy contexts] +ref compiler/GHC/Core/Unfold/Make.hs: Note [DFunUnfoldings] +ref compiler/GHC/Core/Unify.hs: Note [Unification result] +ref compiler/GHC/Core/Unify.hs: Note [INLINE pragmas and (>>)] +ref compiler/GHC/Core/Utils.hs: Note [ _ -> [con1] +ref compiler/GHC/Core/Utils.hs: Note [Interaction of exprIsCheap and lone variables] +ref compiler/GHC/Core/Utils.hs: Note [exprIsHNF Tick] +ref compiler/GHC/Core/Utils.hs: Note [exprIsHNF Tick] +ref compiler/GHC/Core/Utils.hs: Note [Arity care] +ref compiler/GHC/Core/Utils.hs: Note [Arity care] +ref compiler/GHC/CoreToStg.hs: Note [Nullary unboxed tuple] +ref compiler/GHC/CoreToStg/Prep.hs: Note [CorePrep Overview] +ref compiler/GHC/CoreToStg/Prep.hs: Note [Floating Ticks in CorePrep] +ref compiler/GHC/CoreToStg/Prep.hs: Note [Floating Ticks in CorePrep] +ref compiler/GHC/Data/FastString.hs: Note [Updating the FastString table] +ref compiler/GHC/Data/FastString.hs: Note [Updating the FastString table] +ref compiler/GHC/Driver/CmdLine.hs: Note [Handling errors when parsing flags] +ref compiler/GHC/Driver/CmdLine.hs: Note [Handling errors when parsing commandline flags] +ref compiler/GHC/Driver/Flags.hs: Note [Valid hole fits include] +ref compiler/GHC/Driver/Flags.hs: Note [Print Hexadecimal Literals] +ref compiler/GHC/Driver/Main.hs: Note [simpleTidyPgm - mkBootModDetailsTc] +ref compiler/GHC/Driver/Make.hs: Note [Unused packages] +ref compiler/GHC/Driver/Make.hs: Note [GHC Heap Invariants] +ref compiler/GHC/Driver/Make.hs: Note [GHC Heap Invariants] +ref compiler/GHC/Driver/Pipeline/Execute.hs: Note [Clamping of llc optimizations] +ref compiler/GHC/Driver/Pipeline/Execute.hs: Note [Don't normalise input filenames] +ref compiler/GHC/Driver/Pipeline/Execute.hs: Note [Don't normalise input filenames] +ref compiler/GHC/Driver/Session.hs: Note [LLVM Configuration] +ref compiler/GHC/Driver/Session.hs: Note [LLVM Configuration] +ref compiler/GHC/Driver/Session.hs: Note [Handling errors when parsing commandline flags] +ref compiler/GHC/Driver/Session.hs: Note [GHC.Driver.Main . Safe Haskell Inference] +ref compiler/GHC/Driver/Session.hs: Note [Eta-reduction in -O0] +ref compiler/GHC/Driver/Session.hs: Note [No PIE when linking] +ref compiler/GHC/Hs/Expr.hs: Note [Applicative BodyStmt] +ref compiler/GHC/Hs/Expr.hs: Note [Applicative BodyStmt] +ref compiler/GHC/Hs/Extension.hs: Note [Strict argument type constraints] +ref compiler/GHC/HsToCore/Binds.hs: Note [AbsBinds wrappers] +ref compiler/GHC/HsToCore/Binds.hs: Note [Free dictionaries] +ref compiler/GHC/HsToCore/Binds.hs: Note [Free tyvars in rule LHS] +ref compiler/GHC/HsToCore/Binds.hs: Note [Free dictionaries in rule LHS] +ref compiler/GHC/HsToCore/Binds.hs: Note [Free dictionaries] +ref compiler/GHC/HsToCore/Binds.hs: Note [Dead spec binders] +ref compiler/GHC/HsToCore/Coverage.hs: Note [inline sccs] +ref compiler/GHC/HsToCore/Coverage.hs: Note [inline sccs] +ref compiler/GHC/HsToCore/Coverage.hs: Note [inline sccs] +ref compiler/GHC/HsToCore/Coverage.hs: Note [inline sccs] +ref compiler/GHC/HsToCore/Coverage.hs: Note [freevars] +ref compiler/GHC/HsToCore/Docs.hs: Note [1] +ref compiler/GHC/HsToCore/Docs.hs: Note [1] +ref compiler/GHC/HsToCore/Expr.hs: Note [Checking representation-polymorphic data constructors] +ref compiler/GHC/HsToCore/Expr.hs: Note [NOINLINE someNatVal] +ref compiler/GHC/HsToCore/Match.hs: Note [Empty case expressions] +ref compiler/GHC/HsToCore/Match.hs: Note [Case elimination: lifted case] +ref compiler/GHC/HsToCore/Pmc/Desugar.hs: Note [Order of guards matter] +ref compiler/GHC/HsToCore/Pmc/Solver.hs: Note [COMPLETE sets on data families] +ref compiler/GHC/HsToCore/Pmc/Solver.hs: Note [Pos/Neg invariant] +ref compiler/GHC/HsToCore/Pmc/Solver.hs: Note [Soundness and Completeness] +ref compiler/GHC/HsToCore/Pmc/Solver.hs: Note [Soundness and Completeness] +ref compiler/GHC/HsToCore/Types.hs: Note [Generating fresh names for FFI wrappers] +ref compiler/GHC/HsToCore/Types.hs: Note [Note [Long-distance information] +ref compiler/GHC/HsToCore/Utils.hs: Note [MatchIds] +ref compiler/GHC/HsToCore/Utils.hs: Note [Don't CPR join points] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Updating HieAst for changes in the GHC AST] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Capturing Scopes and other non local information] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Name Remapping] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Name Remapping] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Capturing Scopes and other non local information] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [TyVar Scopes] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Scoping Rules for SigPat] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Updating HieAst for changes in the GHC AST] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Name Remapping] +ref compiler/GHC/Iface/Ext/Ast.hs: Note [Scoping Rules for SigPat] +ref compiler/GHC/Iface/Load.hs: Note [GHC Heap Invariants] +ref compiler/GHC/Iface/Recomp.hs: Note [default method Name] +ref compiler/GHC/Iface/Recomp.hs: Note [default method Name] +ref compiler/GHC/Iface/Recomp.hs: Note [default method Name] +ref compiler/GHC/Iface/Recomp/Flags.hs: Note [path flags and recompilation] +ref compiler/GHC/Iface/Recomp/Flags.hs: Note [path flags and recompilation] +ref compiler/GHC/Iface/Syntax.hs: Note [Minimal complete definition] +ref compiler/GHC/Iface/Syntax.hs: Note [Minimal complete definition] +ref compiler/GHC/Linker/Loader.hs: Note [preload packages] +ref compiler/GHC/Linker/Loader.hs: Note [preload packages] +ref compiler/GHC/Linker/Static.hs: Note [No PIE when linking] +ref compiler/GHC/Linker/Types.hs: Note [Grant plan for static forms] +ref compiler/GHC/Parser/Lexer.x: Note [Lexing NumericUnderscores extension] +ref compiler/GHC/Parser/Lexer.x: Note [Lexing NumericUnderscores extension] +ref compiler/GHC/Rename/Env.hs: Note [ Unbound vs Ambiguous Names ] +ref compiler/GHC/Rename/Env.hs: Note [ Unbound vs Ambiguous Names ] +ref compiler/GHC/Rename/Env.hs: Note [ Unbound vs Ambiguous Names ] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo and strict patterns] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo and refutable patterns] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo and strict patterns] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo and strict patterns] +ref compiler/GHC/Rename/Expr.hs: Note [ApplicativeDo and refutable patterns] +ref compiler/GHC/Rename/HsType.hs: Note [CUSKs: Complete user-supplied kind signatures] +ref compiler/GHC/Rename/Pat.hs: Note [Disambiguating record fields] +ref compiler/GHC/Rename/Splice.hs: Note [RunSplice ThLevel] +ref compiler/GHC/Rename/Splice.hs: Note [Splices] +ref compiler/GHC/Rename/Unbound.hs: Note [Only-quals] +ref compiler/GHC/Rename/Unbound.hs: Note [Only-quals] +ref compiler/GHC/Rename/Unbound.hs: Note [Related name spaces] +ref compiler/GHC/Runtime/Eval.hs: Note [Syncing breakpoint info] +ref compiler/GHC/Runtime/Eval.hs: Note [Syncing breakpoint info] +ref compiler/GHC/Runtime/Eval.hs: Note [Querying instances for a type] +ref compiler/GHC/Runtime/Interpreter.hs: Note [Remote GHCi] +ref compiler/GHC/Runtime/Interpreter.hs: Note [External GHCi pointers] +ref compiler/GHC/Runtime/Interpreter.hs: Note [Remote Template Haskell] +ref compiler/GHC/Runtime/Interpreter.hs: Note [uninterruptibleMask_] +ref compiler/GHC/Runtime/Interpreter.hs: Note [uninterruptibleMask_ and interpCmd] +ref compiler/GHC/Runtime/Interpreter.hs: Note [loadObj and relative paths] +ref compiler/GHC/Runtime/Interpreter.hs: Note [loadObj and relative paths] +ref compiler/GHC/Runtime/Interpreter.hs: Note [loadObj and relative paths] +ref compiler/GHC/Runtime/Interpreter.hs: Note [loadObj and relative paths] +ref compiler/GHC/Runtime/Interpreter.hs: Note [External GHCi pointers] +ref compiler/GHC/Settings/IO.hs: Note [tooldir: How GHC finds mingw on Windows] +ref compiler/GHC/StgToByteCode.hs: Note [generating code for top-level string literal bindings] +ref compiler/GHC/StgToByteCode.hs: Note [generating code for top-level string literal bindings] +ref compiler/GHC/StgToByteCode.hs: Note [GHCi unboxed tuples stack spills] +ref compiler/GHC/StgToByteCode.hs: Note [GHCi tuple layout] +ref compiler/GHC/StgToByteCode.hs: Note [CASEFAIL] +ref compiler/GHC/StgToByteCode.hs: Note [CASEFAIL] +ref compiler/GHC/StgToByteCode.hs: Note [generating code for top-level string literal bindings] +ref compiler/GHC/StgToCmm.hs: Note [codegen-split-init] +ref compiler/GHC/StgToCmm.hs: Note [pipeline-split-init] +ref compiler/GHC/StgToCmm/Bind.hs: Note [cgBind rec] +ref compiler/GHC/StgToCmm/Closure.hs: Note [Evaluating functions with profiling] +ref compiler/GHC/StgToCmm/DataCon.hs: Note [About the NameSorts] +ref compiler/GHC/StgToCmm/DataCon.hs: Note [CHARLIKE and INTLIKE closures.] +ref compiler/GHC/StgToCmm/DataCon.hs: Note [About the NameSorts] +ref compiler/GHC/StgToCmm/Expr.hs: Note [case on bool] +ref compiler/GHC/StgToCmm/Expr.hs: Note [dataToTag#] +ref compiler/GHC/StgToCmm/Expr.hs: Note [alg-alt heap check] +ref compiler/GHC/StgToCmm/Foreign.hs: Note [safe foreign call convention] +ref compiler/GHC/StgToCmm/Foreign.hs: Note [safe foreign call convention] +ref compiler/GHC/StgToCmm/Foreign.hs: Note [lower safe foreign calls] +ref compiler/GHC/StgToCmm/Foreign.hs: Note [safe foreign call convention] +ref compiler/GHC/StgToCmm/Foreign.hs: Note [GHCi tuple layout] +ref compiler/GHC/StgToCmm/Heap.hs: Note [STATIC_LINK fields] +ref compiler/GHC/StgToCmm/Heap.hs: Note [stg_gc arguments] +ref compiler/GHC/StgToCmm/Heap.hs: Note [stg_gc arguments] +ref compiler/GHC/StgToCmm/Layout.hs: Note [avoid intermediate PAPs] +ref compiler/GHC/StgToCmm/Layout.hs: Note [diamond proc point] +ref compiler/GHC/StgToCmm/Layout.hs: Note [avoid intermediate PAPs] +ref compiler/GHC/StgToCmm/Layout.hs: Note [over-saturated calls] +ref compiler/GHC/StgToCmm/Layout.hs: Note [over-saturated calls] +ref compiler/GHC/StgToCmm/Monad.hs: Note [sharing continuations] +ref compiler/GHC/StgToCmm/Monad.hs: Note [sharing continuations] +ref compiler/GHC/SysTools.hs: Note [Windows stack usage] +ref compiler/GHC/SysTools/BaseDir.hs: Note [tooldir: How GHC finds mingw on Windows] +ref compiler/GHC/SysTools/BaseDir.hs: Note [tooldir: How GHC finds mingw on Windows] +ref compiler/GHC/SysTools/Info.hs: Note [Run-time linker info] +ref compiler/GHC/SysTools/Info.hs: Note [ELF needed shared libs] +ref compiler/GHC/SysTools/Info.hs: Note [Windows static libGCC] +ref compiler/GHC/SysTools/Info.hs: Note [Run-time linker info] +ref compiler/GHC/SysTools/Info.hs: Note [ELF needed shared libs] +ref compiler/GHC/SysTools/Info.hs: Note [ELF needed shared libs] +ref compiler/GHC/SysTools/Info.hs: Note [ELF needed shared libs] +ref compiler/GHC/SysTools/Info.hs: Note [Windows stack usage] +ref compiler/GHC/SysTools/Info.hs: Note [Windows static libGCC] +ref compiler/GHC/SysTools/Info.hs: Note [Run-time linker info] +ref compiler/GHC/SysTools/Tasks.hs: Note [Run-time linker info] +ref compiler/GHC/Tc/Deriv/Utils.hs: Note [Newtype deriving and unused constructors] +ref compiler/GHC/Tc/Errors.hs: Note [Fail fast on kind errors] +ref compiler/GHC/Tc/Errors.hs: Note [Highlighting ambiguous type variables] +ref compiler/GHC/Tc/Errors/Hole.hs: Note [Relevant Constraints] +ref compiler/GHC/Tc/Errors/Hole.hs: Note [Speeding up valid-hole fits] +ref compiler/GHC/Tc/Errors/Ppr.hs: Note [Highlighting ambiguous type variables] +ref compiler/GHC/Tc/Errors/Types.hs: Note [Migrating TcM messages] +ref compiler/GHC/Tc/Gen/Bind.hs: Note [Existentials in pattern bindings] +ref compiler/GHC/Tc/Gen/Export.hs: Note [Modules without a module header] +ref compiler/GHC/Tc/Gen/Export.hs: Note [Modules without a module header] +ref compiler/GHC/Tc/Gen/Expr.hs: Note [Disambiguating record fields] +ref compiler/GHC/Tc/Gen/Expr.hs: Note [Disambiguating record fields] +ref compiler/GHC/Tc/Gen/Expr.hs: Note [Deprecating ambiguous fields] +ref compiler/GHC/Tc/Gen/Foreign.hs: Note [Expanding newtypes] +ref compiler/GHC/Tc/Gen/HsType.hs: Note [Skolem escape prevention] +ref compiler/GHC/Tc/Gen/HsType.hs: Note [Body kind of HsForAllTy] +ref compiler/GHC/Tc/Gen/HsType.hs: Note [Matching a kind sigature with a declaration] +ref compiler/GHC/Tc/Gen/HsType.hs: Note [Cloning for type variable binder] +ref compiler/GHC/Tc/Gen/Match.hs: Note [GroupStmt binder map] +ref compiler/GHC/Tc/Gen/Match.hs: Note [GroupStmt binder map] +ref compiler/GHC/Tc/Gen/Match.hs: Note [typechecking ApplicativeStmt] +ref compiler/GHC/Tc/Gen/Pat.hs: Note [Typing patterns in pattern bindings] +ref compiler/GHC/Tc/Gen/Pat.hs: Note [Pattern coercions] +ref compiler/GHC/Tc/Gen/Pat.hs: Note [Binding when lookup up instances] +ref compiler/GHC/Tc/Gen/Pat.hs: Note [Matching polytyped patterns] +ref compiler/GHC/Tc/Gen/Pat.hs: Note [Pattern coercions] +ref compiler/GHC/Tc/Gen/Sig.hs: Note [Overview of type signatures] +ref compiler/GHC/Tc/Gen/Sig.hs: Note [solveEqualities in tcPatSynSig] +ref compiler/GHC/Tc/Gen/Splice.hs: Note [RunSplice ThLevel] +ref compiler/GHC/Tc/Gen/Splice.hs: Note [Remote Template Haskell] +ref compiler/GHC/Tc/Gen/Splice.hs: Note [Remote Template Haskell] +ref compiler/GHC/Tc/Gen/Splice.hs: Note [TH recover with -fexternal-interpreter] +ref compiler/GHC/Tc/Gen/Splice.hs: Note [TH recover with -fexternal-interpreter] +ref compiler/GHC/Tc/Instance/Family.hs: Note [Constrained family instances] +ref compiler/GHC/Tc/Instance/FunDeps.hs: Note [Coverage Condition] +ref compiler/GHC/Tc/Module.hs: Note [Extra dependencies from .hs-boot files] +ref compiler/GHC/Tc/Module.hs: Note [Root-main id] +ref compiler/GHC/Tc/Solver.hs: Note [Kind generalisation and SigTvs] +ref compiler/GHC/Tc/Solver/Canonical.hs: Note [The superclasses story] +ref compiler/GHC/Tc/Solver/Canonical.hs: Note [Canonical LHS] +ref compiler/GHC/Tc/Solver/Canonical.hs: Note [Do not decompose given polytype equalities] +ref compiler/GHC/Tc/Solver/Interact.hs: Note [No touchables as FunEq RHS] +ref compiler/GHC/Tc/Solver/Interact.hs: Note [The improvement story] +ref compiler/GHC/Tc/Solver/Interact.hs: Note [The equality class story] +ref compiler/GHC/Tc/Solver/Monad.hs: Note [Speeding up valid-hole fits] +ref compiler/GHC/Tc/Solver/Rewrite.hs: Note [Stability of rewriting] +ref compiler/GHC/Tc/TyCl.hs: Note [Single function non-recursive binding special-case] +ref compiler/GHC/Tc/TyCl.hs: Note [Unification variables need fresh Names] +ref compiler/GHC/Tc/TyCl.hs: Note [TyConBinders for the result kind signatures of a data type] +ref compiler/GHC/Tc/TyCl.hs: Note [rejigCon and c.f. Note [Check role annotations in a second pass] +ref compiler/GHC/Tc/TyCl/Instance.hs: Note [Generalising in tcFamTyPatsGuts] +ref compiler/GHC/Tc/Types.hs: Note [Generating fresh names for FFI wrappers] +ref compiler/GHC/Tc/Types.hs: Note [Extra dependencies from .hs-boot files] +ref compiler/GHC/Tc/Types.hs: Note [RunSplice ThLevel] +ref compiler/GHC/Tc/Types.hs: Note [RunSplice ThLevel] +ref compiler/GHC/Tc/Types.hs: Note [Don't promote data constructors with non-equality contexts] +ref compiler/GHC/Tc/Types.hs: Note [Meaning of IdBindingInfo and ClosedTypeId] +ref compiler/GHC/Tc/Types.hs: Note [Meaning of IdBindingInfo and ClosedTypeId] +ref compiler/GHC/Tc/Types.hs: Note [Bindings with closed types] +ref compiler/GHC/Tc/Types.hs: Note [Care with plugin imports] +ref compiler/GHC/Tc/Types/Constraint.hs: Note [NonCanonical Semantics] +ref compiler/GHC/Tc/Types/Constraint.hs: Note [The improvement story] +ref compiler/GHC/Tc/Utils/Concrete.hs: Note [Concrete and Concrete#] +ref compiler/GHC/Tc/Utils/Env.hs: Note [Bindings with closed types] +ref compiler/GHC/Tc/Utils/Env.hs: Note [Generating fresh names for ccall wrapper] +ref compiler/GHC/Tc/Utils/Env.hs: Note [Generating fresh names for FFI wrappers] +ref compiler/GHC/Tc/Utils/Env.hs: Note [Placeholder PatSyn kinds] +ref compiler/GHC/Tc/Utils/TcMType.hs: Note [Kind checking for GADTs] +ref compiler/GHC/Tc/Utils/TcType.hs: Note [TyVars and TcTyVars] +ref compiler/GHC/Tc/Utils/Unify.hs: Note [Unification preconditions, (TYVAR-TV)] +ref compiler/GHC/Tc/Utils/Zonk.hs: Note [Rebindable Syntax and HsExpansion] +ref compiler/GHC/ThToHs.hs: Note [Operator association] +ref compiler/GHC/ThToHs.hs: Note [Operator association] +ref compiler/GHC/ThToHs.hs: Note [Operator association] +ref compiler/GHC/ThToHs.hs: Note [Adding parens for splices] +ref compiler/GHC/ThToHs.hs: Note [Adding parens for splices] +ref compiler/GHC/Types/Basic.hs: Note [Safe Haskell isSafeOverlap] +ref compiler/GHC/Types/Basic.hs: Note [Activation competition] +ref compiler/GHC/Types/Demand.hs: Note [Preserving Boxity of results is rarely a win] +ref compiler/GHC/Types/Demand.hs: Note [Use one-shot information] +ref compiler/GHC/Types/Error.hs: Note [Suppressing Messages] +ref compiler/GHC/Types/Error.hs: Note [Suppressing Messages] +ref compiler/GHC/Types/Id/Make.hs: Note [Left folds via right fold] +ref compiler/GHC/Types/Name.hs: Note [About the NameSorts] +ref compiler/GHC/Types/Name.hs: Note [About the NameSorts] +ref compiler/GHC/Types/Name/Occurrence.hs: Note [Data Constructors] +ref compiler/GHC/Types/Name/Occurrence.hs: Note [Unique OccNames from Template Haskell] +ref compiler/GHC/Types/SourceText.hs: Note [Fractional exponent bases] +ref compiler/GHC/Types/Tickish.hs: Note [Tickish passes] +ref compiler/GHC/Types/Tickish.hs: Note [Tickish passes] +ref compiler/GHC/Types/Unique.hs: Note [Uniques-prelude - Uniques for wired-in Prelude things] +ref compiler/GHC/Types/Var.hs: Note [Promoted GADT data construtors] +ref compiler/GHC/Types/Var/Env.hs: Note [Rebinding] +ref compiler/GHC/Unit/Info.hs: Note [About units] +ref compiler/GHC/Unit/Module/Deps.hs: Note [Structure of dep_boot_mods] +ref compiler/GHC/Unit/State.hs: Note [About units] +ref compiler/GHC/Unit/State.hs: Note [About units] +ref compiler/GHC/Unit/State.hs: Note [About units] +ref compiler/GHC/Unit/State.hs: Note [Representation of module/name variable] +ref compiler/GHC/Unit/State.hs: Note [Representation of module/name variable] +ref compiler/GHC/Utils/Monad.hs: Note [multiShotIO] +ref compiler/GHC/Utils/Monad.hs: Note [inlineIdMagic] +ref compiler/GHC/Utils/Outputable.hs: Note [Print Hexadecimal Literals] +ref compiler/GHC/Utils/Ppr.hs: Note [Differences between libraries/pretty and compiler/GHC/Utils/Ppr.hs] +ref compiler/GHC/Utils/Ppr.hs: Note [Print Hexadecimal Literals] +ref compiler/GHC/Utils/Ppr.hs: Note [Print Hexadecimal Literals] +ref compiler/Language/Haskell/Syntax/Binds.hs: Note [fun_id in Match] +ref compiler/Language/Haskell/Syntax/Decls.hs: Note [TyVar binders for associated declarations] +ref compiler/Language/Haskell/Syntax/Decls.hs: Note [TyVar binders for associated declarations] +ref compiler/Language/Haskell/Syntax/Expr.hs: Note [Record Selectors in the AST] +ref compiler/Language/Haskell/Syntax/Expr.hs: Note [Record Selectors in the AST] +ref compiler/Language/Haskell/Syntax/Expr.hs: Note [ApplicativeDo] +ref compiler/Language/Haskell/Syntax/Expr.hs: Note [Applicative BodyStmt] +ref compiler/Language/Haskell/Syntax/Expr.hs: Note [Applicative BodyStmt] +ref compiler/Language/Haskell/Syntax/Expr.hs: Note [Quasi-quote overview] +ref compiler/Language/Haskell/Syntax/Extension.hs: Note [Constructor cannot happen] +ref compiler/Language/Haskell/Syntax/Pat.hs: Note [Disambiguating record fields] +ref compiler/Language/Haskell/Syntax/Type.hs: Note [HsArgPar] +ref compiler/Language/Haskell/Syntax/Type.hs: Note [HsArgPar] +ref compiler/ghc.mk: Note [Stage1Only vs stage=1] +ref configure.ac: Note [Linking ghc-bin against threaded stage0 RTS] +ref configure.ac: Note [tooldir: How GHC finds mingw on Windows] +ref configure.ac: Note [tooldir: How GHC finds mingw on Windows] +ref docs/core-spec/core-spec.mng: Note [TyBinders] +ref docs/core-spec/core-spec.mng: Note [Unused coercion variable in ForAllCo] +ref ghc.mk: Note [No stage2 packages when CrossCompiling or Stage1Only] +ref ghc.mk: Note [No stage2 packages when CrossCompiling or Stage1Only] +ref ghc.mk: Note [Stage1Only vs stage=1] +ref ghc.mk: Note [Stage1Only vs stage=1] +ref ghc.mk: Note [Dependencies between package-data.mk files] +ref ghc.mk: Note [No stage2 packages when CrossCompiling or Stage1Only] +ref ghc.mk: Note [Stage1Only vs stage=1] +ref ghc.mk: Note [No stage2 packages when CrossCompiling or Stage1Only] +ref ghc.mk: Note [No stage2 packages when CrossCompiling or Stage1Only] +ref ghc.mk: Note [CrossCompiling vs Stage1Only] +ref ghc.mk: Note [Stage1Only vs stage=1] +ref ghc/GHCi/UI.hs: Note [Changing language extensions for interactive evaluation] +ref ghc/GHCi/UI.hs: Note [ModBreaks.decls] +ref ghc/Main.hs: Note [Handling errors when parsing commandline flags] +ref ghc/ghc.mk: Note [Linking ghc-bin against threaded stage0 RTS] +ref ghc/ghc.mk: Note [Stage1Only vs stage=1] +ref ghc/ghc.mk: Note [Stage1Only vs stage=1] +ref hadrian/cfg/system.config.in: Note [tooldir: How GHC finds mingw on Windows] +ref hadrian/src/Expression.hs: Note [Linking ghc-bin against threaded stage0 RTS] +ref hadrian/src/Oracles/Setting.hs: Note [tooldir: How GHC finds mingw on Windows] +ref hadrian/src/Rules/Generate.hs: Note [tooldir: How GHC finds mingw on Windows] +ref hadrian/src/Rules/Libffi.hs: Note [Libffi indicating inputs] +ref libraries/base/Control/Concurrent/QSem.hs: Note [signal uninterruptible] +ref libraries/base/Control/Concurrent/QSem.hs: Note [signal uninterruptible] +ref libraries/base/Control/Concurrent/QSem.hs: Note [signal uninterruptible] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST: not producing lazy pairs] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST and multithreading] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST: not producing lazy pairs] +ref libraries/base/Control/Monad/ST/Lazy/Imp.hs: Note [Lazy ST: not producing lazy pairs] +ref libraries/base/Data/OldList.hs: Note [Left folds via right fold] +ref libraries/base/Data/OldList.hs: Note [INLINE unfoldr] +ref libraries/base/Data/OldList.hs: Note [INLINE unfoldr] +ref libraries/base/GHC/Enum.hs: Note [Enum Integer rules for literal 1] +ref libraries/base/GHC/Event/Windows.hsc: Note [Completion Ports] +ref libraries/base/GHC/Event/Windows.hsc: Note [Completion Ports] +ref libraries/base/GHC/Event/Windows.hsc: Note [Memory Management] +ref libraries/base/GHC/Event/Windows.hsc: Note [Memory Management] +ref libraries/base/GHC/Event/Windows/FFI.hsc: Note [Completion Ports] +ref libraries/base/GHC/ForeignPtr.hs: Note [Why FinalPtr] +ref libraries/base/GHC/ForeignPtr.hs: Note [Why FinalPtr] +ref libraries/base/GHC/ForeignPtr.hs: Note [MallocPtr finalizers] +ref libraries/base/GHC/ForeignPtr.hs: Note [MallocPtr finalizers] +ref libraries/base/GHC/ForeignPtr.hs: Note [MallocPtr finalizers] +ref libraries/base/GHC/IO/FD.hs: Note [nonblock] +ref libraries/base/GHC/IO/Handle/Internals.hs: Note [async] +ref libraries/base/GHC/IO/Handle/Internals.hs: Note [async] +ref libraries/base/GHC/IO/Handle/Text.hs: Note [#5536] +ref libraries/base/GHC/IO/Windows/Handle.hsc: Note [ReadFile/WriteFile] +ref libraries/base/GHC/IO/Windows/Handle.hsc: Note [ReadFile/WriteFile] +ref libraries/base/GHC/IO/Windows/Handle.hsc: Note [ReadFile/WriteFile] +ref libraries/base/GHC/IO/Windows/Handle.hsc: Note [ReadFile/WriteFile] +ref libraries/base/GHC/IO/Windows/Handle.hsc: Note [ReadFile/WriteFile] +ref libraries/base/GHC/List.hs: Note [Left folds via right fold] +ref libraries/base/GHC/List.hs: Note [Left folds via right fold] +ref libraries/base/GHC/List.hs: Note [Left fold via right fold] +ref libraries/base/GHC/List.hs: Note [Left folds via right fold] +ref libraries/base/GHC/List.hs: Note [Left folds via right fold] +ref libraries/base/GHC/List.hs: Note [Left folds via right fold] +ref libraries/base/GHC/List.hs: Note [scanrFB and evaluation] +ref libraries/base/GHC/List.hs: Note [scanrFB and evaluation] +ref libraries/base/GHC/List.hs: Note [Fusion for foldr2] +ref libraries/base/GHC/List.hs: Note [Fusion for foldr2] +ref libraries/base/GHC/Read.hs: Note [Why readField] +ref libraries/base/GHC/Read.hs: Note [Why readField] +ref libraries/base/GHC/Read.hs: Note [Why readField] +ref libraries/base/GHC/Read.hs: Note [Why readField] +ref libraries/base/GHC/Real.hs: Note [Numeric Stability of Enumerating Floating Numbers] +ref libraries/base/GHC/Real.hs: Note [Numeric Stability of Enumerating Floating Numbers] +ref libraries/base/GHC/Real.hs: Note [Numeric Stability of Enumerating Floating Numbers] +ref libraries/base/GHC/ST.hs: Note [Definition of runRW#] +ref libraries/base/GHC/TypeLits.hs: Note [NOINLINE someNatVal] +ref libraries/base/GHC/TypeNats.hs: Note [NOINLINE someNatVal] +ref libraries/base/GHC/TypeNats.hs: Note [NOINLINE someNatVal] +ref libraries/base/Unsafe/Coerce.hs: Note [Implementing unsafeCorece] +ref libraries/base/cbits/inputReady.c: Note [Guaranteed syscall time spent] +ref libraries/base/cbits/inputReady.c: Note [Guaranteed syscall time spent] +ref libraries/ghc-prim/GHC/Types.hs: Note [Linear Types] +ref libraries/ghci/GHCi/Message.hs: Note [Remote GHCi] +ref libraries/ghci/GHCi/Message.hs: Note [Remote Template Haskell] +ref libraries/ghci/GHCi/Message.hs: Note [Remote Template Haskell] +ref libraries/ghci/GHCi/RemoteTypes.hs: Note [External GHCi pointers] +ref libraries/ghci/GHCi/RemoteTypes.hs: Note [Remote GHCi] +ref libraries/ghci/GHCi/Run.hs: Note [Remote GHCi] +ref libraries/ghci/GHCi/TH.hs: Note [Remote Template Haskell] +ref libraries/ghci/GHCi/TH.hs: Note [Remote GHCi] +ref libraries/ghci/GHCi/TH.hs: Note [External GHCi pointers] +ref libraries/ghci/GHCi/TH.hs: Note [TH recover with -fexternal-interpreter] +ref libraries/ghci/GHCi/TH.hs: Note [TH recover with -fexternal-interpreter] +ref libraries/libiserv/src/IServ.hs: Note [Remote Template Haskell] +ref m4/fp_settings.m4: Note [tooldir: How GHC finds mingw on Windows] +ref mk/config.mk.in: Note [Stage number in build variables] +ref mk/config.mk.in: Note [Stage number in build variables] +ref mk/config.mk.in: Note [Stage number in build variables] +ref mk/config.mk.in: Note [Stage number in build variables] +ref mk/config.mk.in: Note [tooldir: How GHC finds mingw on Windows] +ref mk/config.mk.in: Note [CrossCompiling vs Stage1Only] +ref mk/config.mk.in: Note [CrossCompiling vs Stage1Only] +ref mk/config.mk.in: Note [Stage1Only vs stage=1] +ref mk/config.mk.in: Note [CrossCompiling vs Stage1Only] +ref mk/config.mk.in: Note [Stage1Only vs stage=1] +ref mk/config.mk.in: Note [Stage1Only vs stage=1] +ref mk/config.mk.in: Note [Stage1Only vs stage=1] +ref mk/config.mk.in: Note [No stage2 packages when CrossCompiling or Stage1Only] +ref mk/config.mk.in: Note [Disable -O2 in unregisterised mode] +ref mk/config.mk.in: Note [Disable -O2 in unregisterised mode] +ref mk/tree.mk: Note [Spaces in TEST_HC] +ref mk/warnings.mk: Note [Order of warning flags] +ref mk/warnings.mk: Note [Stage number in build variables] +ref mk/warnings.mk: Note [Order of warning flags] +ref rts/Apply.cmm: Note [Evaluating functions with profiling] +ref rts/Apply.cmm: Note [suspend duplicate work] +ref rts/Capability.c: Note [GC livelock] +ref rts/Capability.h: Note [allocation accounting] +ref rts/Compact.cmm: Note [compactAddWorker result] +ref rts/Compact.cmm: Note [compactAddWorker result] +ref rts/Interpreter.c: Note [Not true: ASSERT(Sp > SpLim)] +ref rts/Interpreter.c: Note [avoiding threadPaused] +ref rts/Interpreter.c: Note [upd-black-hole] +ref rts/Interpreter.c: Note [Evaluating functions with profiling] +ref rts/Interpreter.c: Note [Evaluating functions with profiling] +ref rts/Linker.c: Note [runtime-linker-support] +ref rts/Linker.c: Note [runtime-linker-phases] +ref rts/Linker.c: Note [weak-symbols-support] +ref rts/Linker.c: Note [RTLD_LOCAL] +ref rts/Linker.c: Note [RTLD_LOCAL] +ref rts/Linker.c: Note [runtime-linker-phases] +ref rts/Linker.c: Note [loadOc orderings] +ref rts/LinkerInternals.h: Note [No typedefs for customizable types] +ref rts/LinkerInternals.h: Note [No typedefs for customizable types] +ref rts/LinkerInternals.h: Note [TLSGD relocation] +ref rts/LinkerInternals.h: Note [No typedefs for customizable types] +ref rts/Messages.c: Note [BLACKHOLE pointing to IND] +ref rts/PrimOps.cmm: Note [Nonmoving write barrier in Perform{Put,Take}] +ref rts/PrimOps.cmm: Note [Nonmoving write barrier in Perform{Put,Take}] +ref rts/RaiseAsync.c: Note [Throw to self when masked] +ref rts/RtsFlags.c: Note [OPTION_SAFE vs OPTION_UNSAFE] +ref rts/RtsFlags.c: Note [OPTION_SAFE vs OPTION_UNSAFE] +ref rts/Schedule.c: Note [shutdown] +ref rts/Schedule.c: Note [GC livelock] +ref rts/Schedule.c: Note [GC livelock] +ref rts/Schedule.c: Note [avoiding threadPaused] +ref rts/Schedule.c: Note [Deadlock detection under nonmoving collector] +ref rts/Schedule.h: Note [shutdown] +ref rts/Sparks.c: Note [STATIC_LINK fields] +ref rts/StablePtr.c: Note [Enlarging the stable pointer table] +ref rts/StablePtr.c: Note [Enlarging the stable pointer table] +ref rts/Stats.c: Note [n_gc_threads] +ref rts/Stats.c: Note [RTS Stats Reporting] +ref rts/Stats.c: Note [RTS Stats Reporting] +ref rts/Stats.c: Note [Work Balance] +ref rts/Stats.c: Note [Internal Counter Stats] +ref rts/Stats.c: Note [RTS Stats Reporting] +ref rts/Stats.c: Note [RTS Stats Reporting] +ref rts/Stats.c: Note [Work Balance] +ref rts/Stats.c: Note [Work Balance] +ref rts/Stats.c: Note [Internal Counters Stats] +ref rts/StgCRun.c: Note [Windows Stack allocations] +ref rts/StgCRun.c: Note [Windows Stack allocations] +ref rts/StgCRun.c: Note [Windows Stack allocations] +ref rts/StgMiscClosures.cmm: Note [GHCi unboxed tuples stack spills] +ref rts/StgMiscClosures.cmm: Note [GHCi tuple layout] +ref rts/StgMiscClosures.cmm: Note [BLACKHOLE pointing to IND] +ref rts/StgMiscClosures.cmm: Note [suspend duplicate work] +ref rts/StgMiscClosures.cmm: Note [CHARLIKE and INTLIKE closures.] +ref rts/StgStartup.cmm: Note [avoiding threadPaused] +ref rts/StgStdThunks.cmm: Note [untag for prof] +ref rts/StgStdThunks.cmm: Note [untag for prof] +ref rts/StgStdThunks.cmm: Note [untag for prof] +ref rts/ThreadPaused.c: Note [upd-black-hole] +ref rts/ThreadPaused.c: Note [suspend duplicate work] +ref rts/Threads.c: Note [Throw to self when masked] +ref rts/Timer.c: Note [GC During Idle Time] +ref rts/Updates.cmm: Note [HpAlloc] +ref rts/Updates.cmm: Note [HpAlloc] +ref rts/Updates.cmm: Note [HpAlloc] +ref rts/include/Cmm.h: Note [Evaluating functions with profiling] +ref rts/include/Cmm.h: Note [Syntax of .cmm files] +ref rts/include/Stg.h: Note [Windows Stack allocations] +ref rts/include/ghc.mk: Note [tooldir: How GHC finds mingw on Windows] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [MADV_FREE and MADV_DONTNEED] +ref rts/include/rts/Flags.h: Note [Internal Counter Stats] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Flags.h: Note [Synchronization of flags and base APIs] +ref rts/include/rts/Linker.h: Note [runtime-linker-phases] +ref rts/include/rts/OSThreads.h: Note [SRW locks] +ref rts/include/rts/OSThreads.h: Note [SRW locks] +ref rts/include/rts/prof/CCS.h: Note [struct alignment] +ref rts/include/rts/prof/CCS.h: Note [struct alignment] +ref rts/include/rts/prof/CCS.h: Note [struct alignment] +ref rts/include/rts/prof/CCS.h: Note [struct alignment] +ref rts/include/rts/prof/CCS.h: Note [struct alignment] +ref rts/include/rts/storage/Block.h: Note [integer overflow] +ref rts/include/rts/storage/Block.h: Note [integer overflow] +ref rts/include/rts/storage/Block.h: Note [integer overflow] +ref rts/include/rts/storage/Closures.h: Note [CAF lists] +ref rts/include/rts/storage/Closures.h: Note [CAF lists] +ref rts/include/rts/storage/GC.h: Note [allocation accounting] +ref rts/include/stg/MachRegs.h: Note [Overlapping global registers] +ref rts/linker/Elf.c: Note [Many ELF Sections] +ref rts/linker/Elf.c: Note [Many ELF Sections] +ref rts/linker/Elf.c: Note [Many ELF Sections] +ref rts/linker/Elf.c: Note [PC bias] +ref rts/linker/Elf.c: Note [TLSGD relocation] +ref rts/linker/Elf.c: Note [Many ELF Sections] +ref rts/linker/Elf.c: Note [.LCTOC1 in PPC PIC code] +ref rts/linker/Elf.c: Note [Many ELF Sections] +ref rts/linker/LoadArchive.c: Note [MSVC import files (ext .lib)] +ref rts/linker/PEi386.c: Note [mingw-w64 name decoration scheme] +ref rts/linker/PEi386.c: Note [ELF constant in PE file] +ref rts/linker/PEi386.c: Note [mingw-w64 name decoration scheme] +ref rts/linker/PEi386.h: Note [mingw-w64 name decoration scheme] +ref rts/linker/PEi386.h: Note [mingw-w64 name decoration scheme] +ref rts/linker/PEi386.h: Note [mingw-w64 name decoration scheme] +ref rts/linker/SymbolExtras.c: Note [TLSGD relocation] +ref rts/linker/elf_reloc_aarch64.c: Note [PC bias aarch64] +ref rts/linker/elf_tlsgd.c: Note [TLSGD relocation] +ref rts/posix/OSMem.c: Note [MADV_FREE and MADV_DONTNEED] +ref rts/posix/OSMem.c: Note [MADV_FREE and MADV_DONTNEED] +ref rts/sm/Evac.c: Note [Deadlock detection under nonmoving collector] +ref rts/sm/Evac.c: Note [Deadlock detection under nonmoving collector] +ref rts/sm/Evac.c: Note [STATIC_LINK fields] +ref rts/sm/Evac.c: Note [BLACKHOLE pointing to IND] +ref rts/sm/Evac.c: Note [upd-black-hole] +ref rts/sm/GC.c: Note [STATIC_LINK fields] +ref rts/sm/GC.c: Note [Synchronising work stealing] +ref rts/sm/GC.c: Note [n_gc_threads] +ref rts/sm/GC.c: Note [Deadlock detection under nonmoving collector] +ref rts/sm/GC.c: Note [Synchronising work stealing] +ref rts/sm/GC.c: Note [n_gc_threads] +ref rts/sm/GC.c: Note [Work Balance] +ref rts/sm/GC.c: Note [Scaling retained memory] +ref rts/sm/GC.c: Note [Synchronising work stealing] +ref rts/sm/GC.c: Note [Synchronising work stealing] +ref rts/sm/GC.c: Note [Synchronising work stealing] +ref rts/sm/GC.c: Note [STATIC_LINK fields] +ref rts/sm/GC.c: Note [Synchronising work stealing] +ref rts/sm/GC.c: Note [Scaling retained memory] +ref rts/sm/GC.h: Note [Deadlock detection under nonmoving collector] +ref rts/sm/GCUtils.c: Note [big objects] +ref rts/sm/GCUtils.c: Note [big objects] +ref rts/sm/GCUtils.c: Note [big objects] +ref rts/sm/GCUtils.c: Note [big objects] +ref rts/sm/MarkWeak.c: Note [MallocPtr finalizers] +ref rts/sm/NonMovingMark.c: Note [Deadlock detection under nonmoving collector] +ref rts/sm/NonMovingMark.c: Note [Update rememembered set] +ref rts/sm/NonMovingMark.c: Note [upd-black-hole] +ref rts/sm/Scav.c: Note [Deadlock detection under nonmoving collector] +ref rts/sm/Scav.c: Note [upd-black-hole] +ref rts/sm/Scav.c: Note [avoiding threadPaused] +ref rts/sm/Storage.c: Note [STATIC_LINK fields] +ref rts/sm/Storage.c: Note [STATIC_LINK fields] +ref rts/sm/Storage.c: Note [dyn_caf_list] +ref rts/sm/Storage.c: Note [allocation accounting] +ref rts/sm/Storage.h: Note [STATIC_LINK fields] +ref rts/sm/Storage.h: Note [CAF lists] +ref rts/sm/Storage.h: Note [CAF lists] +ref rts/sm/Storage.h: Note [dyn_caf_list] +ref rts/win32/OSMem.c: Note [base memory] +ref rules/build-package-way.mk: Note [inconsistent distdirs] +ref rules/build-package.mk: Note [inconsistent distdirs] +ref rules/build-package.mk: Note [inconsistent distdirs] +ref rules/build-prog.mk: Note [inconsistent distdirs] +ref rules/build-prog.mk: Note [lib-depends] +ref rules/build-prog.mk: Note [inconsistent distdirs] +ref rules/distdir-way-opts.mk: Note [Stage number in build variables] +ref rules/haddock.mk: Note [inconsistent distdirs] +ref rules/hs-suffix-way-rules.mk: Note [Implicit rule search algorithm] +ref testsuite/config/ghc: Note [WayFlags] +ref testsuite/driver/runtests.py: Note [Mutating config.only] +ref testsuite/driver/runtests.py: Note [Running tests in /tmp] +ref testsuite/driver/testglobals.py: Note [validate and testsuite speed] +ref testsuite/driver/testglobals.py: Note [Haddock runtime stats files] +ref testsuite/driver/testglobals.py: Note [Running tests in /tmp] +ref testsuite/driver/testlib.py: Note [Why is there no stage1 setup function?] +ref testsuite/driver/testlib.py: Note [Why is there no stage1 setup function?] +ref testsuite/driver/testlib.py: Note [Mutating config.only] +ref testsuite/driver/testlib.py: Note [validate and testsuite speed] +ref testsuite/driver/testlib.py: Note [Universal newlines] +ref testsuite/driver/testlib.py: Note [Universal newlines] +ref testsuite/driver/testlib.py: Note [Universal newlines] +ref testsuite/driver/testlib.py: Note [Universal newlines] +ref testsuite/driver/testlib.py: Note [Output comparison] +ref testsuite/driver/testlib.py: Note [Null device handling] +ref testsuite/driver/testlib.py: Note [Output comparison] +ref testsuite/driver/testlib.py: Note [Null device handling] +ref testsuite/driver/testlib.py: Note [Output comparison] +ref testsuite/driver/testlib.py: Note [Output comparison] +ref testsuite/driver/testlib.py: Note [Null device handling] +ref testsuite/mk/boilerplate.mk: Note [Communicating options and variables to a submake] +ref testsuite/mk/boilerplate.mk: Note [Spaces in TEST_HC] +ref testsuite/mk/boilerplate.mk: Note [Spaces in TEST_HC] +ref testsuite/mk/boilerplate.mk: Note [Spaces in TEST_HC] +ref testsuite/mk/boilerplate.mk: Note [The TEST_HC variable] +ref testsuite/mk/boilerplate.mk: Note [WayFlags] +ref testsuite/mk/test.mk: Note [Running tests in /tmp] +ref testsuite/mk/test.mk: Note [validate and testsuite speed] +ref testsuite/mk/test.mk: Note [Communicating options and variables to a submake] +ref testsuite/mk/test.mk: Note [validate and testsuite speed] +ref testsuite/mk/test.mk: Note [Communicating options and variables to a submake] +ref testsuite/mk/test.mk: Note [The TEST_HC variable] +ref testsuite/tests/ghci/scripts/T19667Ghci.hs: Note [NOINLINE someNatVal] +ref testsuite/tests/indexed-types/should_compile/T18875.hs: Note [Type variable cycles in Givens] +ref testsuite/tests/indexed-types/should_fail/ExtraTcsUntch.hs: Note [Extra TcS Untouchables] +ref testsuite/tests/perf/haddock/all.T: Note [Haddock runtime stats files] +ref testsuite/tests/perf/join_points/join005.hs: Note [Don't CPR join points] +ref testsuite/tests/perf/should_run/all.T: Note [Solving from instances when interacting Dicts] +ref testsuite/tests/polykinds/CuskFam.hs: Note [Unifying implicit CUSK variables] +ref testsuite/tests/rts/linker/T11223/all.T: Note [weak-symbols-support] +ref testsuite/tests/simplCore/should_compile/T5776.hs: Note [Simplifying RULE lhs constraints] +ref testsuite/tests/simplCore/should_compile/simpl018.hs: Note [Float coercions (unlifted)] +ref testsuite/tests/stranal/sigs/T19871.hs: Note [Boxity Analysis] +ref testsuite/tests/typecheck/should_compile/CbvOverlap.hs: Note [Type variable cycles in Givens] +ref testsuite/tests/typecheck/should_compile/Improvement.hs: Note [No reduction for Derived class constraints] +ref testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs: Note [When does an implication have given equalities?] +ref testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs: Note [Type variable cycles in Givens] +ref testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs: Note [When does an implication have given equalities?] +ref testsuite/tests/typecheck/should_compile/T9117.hs: Note [Order of Coercible Instances] +ref testsuite/tests/typecheck/should_compile/tc200.hs: Note [Multiple instantiation] +ref testsuite/tests/typecheck/should_compile/tc228.hs: Note [Inference and implication constraints] +ref testsuite/tests/typecheck/should_compile/tc231.hs: Note [Important subtlety in oclose] +ref testsuite/tests/typecheck/should_fail/UnliftedNewtypesMultiFieldGadt.hs: Note [Kind-checking the field type] +ref testsuite/tests/typecheck/should_fail/tcfail093.hs: Note [Important subtlety in oclose] +ref testsuite/tests/typecheck/should_run/T16646.hs: Note [NOINLINE someNatVal] +ref testsuite/tests/typecheck/should_run/T19667.hs: Note [NOINLINE someNatVal] +ref utils/genapply/Main.hs: Note [jump_SAVE_CCCS] +ref utils/genapply/Main.hs: Note [jump_SAVE_CCCS] +ref utils/genapply/Main.hs: Note [jump_SAVE_CCCS] +ref utils/ghc-cabal/Main.hs: Note [Msys2 path translation bug] +ref utils/ghc-cabal/Main.hs: Note [Msys2 path translation bug] +ref utils/ghc-pkg/Main.hs: Note [Settings File] +ref utils/ghc-pkg/ghc.mk: Note [Why build certain utils twice?] +ref utils/ghc-pkg/ghc.mk: Note [Stage1Only vs stage=1] +ref utils/ghc-pkg/ghc.mk: Note [Why build certain utils twice?] +ref utils/ghc-pkg/ghc.mk: Note [Stage1Only vs stage=1] +ref utils/iserv/src/Main.hs: Note [Remote GHCi] +ref utils/llvm-targets/gen-data-layout.sh: Note [LLVM Configuration] +ref utils/notes-util/Notes.hs: Note [" <> T.unpack x <> "] +ref utils/notes-util/Notes.hs: Note [...] +ref utils/notes-util/test: Note [This is a Note reference broken across lines] +ref utils/notes-util/test: Note [Broken across a line in a C++ comment] +ref utils/notes-util/test: Note [Broken across a line in a C comment] +ref utils/notes-util/test: Note [Broken across a line in a Haskell comment] +ref utils/notes-util/test: Note [Broken across a line in a Python comment] +ref validate: Note [Default build system verbosity] +ref validate: Note [Default build system verbosity] +ref validate: Note [Default build system verbosity] +ref validate: Note [Running tests in /tmp] +ref validate: Note [Why is there no stage1 setup function?] + diff --git a/utils/notes-util/notes-util.cabal b/utils/notes-util/notes-util.cabal new file mode 100644 index 0000000000..643fd163fd --- /dev/null +++ b/utils/notes-util/notes-util.cabal @@ -0,0 +1,20 @@ +cabal-version: 2.4 +name: notes-util +version: 0.1.0.0 +synopsis: A tool for querying and checking GHC Notes +bug-reports: https://gitlab.haskell.org/ghc/ghc +license: BSD-3-Clause +author: Ben Gamari +maintainer: ben@smart-cactus.org +copyright: (c) 2022 Ben Gamari + +executable ghc-notes + main-is: Main.hs + other-modules: Notes + build-depends: base >= 4 && < 5 , + bytestring, + containers, + directory, + text, + process + default-language: Haskell2010 diff --git a/utils/notes-util/test b/utils/notes-util/test new file mode 100644 index 0000000000..3eb1e0466e --- /dev/null +++ b/utils/notes-util/test @@ -0,0 +1,25 @@ +Note [Turtles] +~~~~~~~~~~~~~~~ +This is note 1. See Note [Wombats are toes]. + +/* Note [Wombats are toes] + ~~~~~~~~~~~~~~~~~~~~~~~ + This is another Note. + */ + +See Note [This is a +Note reference broken across lines]. + + // This is another Note [Broken + // across a line in a C++ comment]. + + /* + * This is another Note [Broken + * across a line in a C comment]. + */ + + -- This is another Note [Broken + -- across a line in a Haskell comment]. + + # This is another Note [Broken + # across a line in a Python comment]. |