summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBrian Wignall <brianwignall@gmail.com>2021-02-05 09:03:21 -0500
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-02-06 09:30:34 -0500
commit3da472f0e78fe5f1068be0cc2b1c0762532da9f9 (patch)
treed88a147c49aa25fff13866de9b87c712213fbd3f
parent9b7dcd80f16efda57e4e51e39d61b55a11c72014 (diff)
downloadhaskell-3da472f0e78fe5f1068be0cc2b1c0762532da9f9.tar.gz
Fix typos
-rw-r--r--compiler/GHC.hs2
-rw-r--r--compiler/GHC/Builtin/PrimOps.hs2
-rw-r--r--compiler/GHC/Cmm/CLabel.hs2
-rw-r--r--compiler/GHC/Cmm/Info/Build.hs2
-rw-r--r--compiler/GHC/CmmToAsm/BlockLayout.hs2
-rw-r--r--compiler/GHC/CmmToAsm/Reg/Graph/Base.hs2
-rw-r--r--compiler/GHC/CmmToAsm/X86/CodeGen.hs2
-rw-r--r--compiler/GHC/Core/Lint.hs4
-rw-r--r--compiler/GHC/Core/Opt/Arity.hs4
-rw-r--r--compiler/GHC/Core/Opt/DmdAnal.hs6
-rw-r--r--compiler/GHC/Core/Opt/OccurAnal.hs4
-rw-r--r--compiler/GHC/Core/Opt/Simplify.hs2
-rw-r--r--compiler/GHC/Core/Opt/Simplify/Utils.hs2
-rw-r--r--compiler/GHC/Core/Opt/Specialise.hs2
-rw-r--r--compiler/GHC/Core/TyCo/FVs.hs2
-rw-r--r--compiler/GHC/Core/TyCo/Rep.hs2
-rw-r--r--compiler/GHC/Core/Type.hs2
-rw-r--r--compiler/GHC/Core/Unfold.hs2
-rw-r--r--compiler/GHC/Core/Unify.hs2
-rw-r--r--compiler/GHC/CoreToStg/Prep.hs2
-rw-r--r--compiler/GHC/HsToCore/Expr.hs4
-rw-r--r--compiler/GHC/Iface/UpdateIdInfos.hs2
-rw-r--r--compiler/GHC/Linker/MacOS.hs2
-rw-r--r--compiler/GHC/Parser/Errors.hs8
-rw-r--r--compiler/GHC/Parser/Lexer.x2
-rw-r--r--compiler/GHC/Parser/PostProcess/Haddock.hs4
-rw-r--r--compiler/GHC/Rename/Env.hs2
-rw-r--r--compiler/GHC/Runtime/Interpreter.hs2
-rw-r--r--compiler/GHC/StgToCmm/Foreign.hs2
-rw-r--r--compiler/GHC/Tc/Deriv/Generate.hs2
-rw-r--r--compiler/GHC/Tc/Gen/App.hs6
-rw-r--r--compiler/GHC/Tc/Gen/Bind.hs2
-rw-r--r--compiler/GHC/Tc/Gen/HsType.hs10
-rw-r--r--compiler/GHC/Tc/Gen/Pat.hs2
-rw-r--r--compiler/GHC/Tc/Solver.hs4
-rw-r--r--compiler/GHC/Tc/Solver/Interact.hs4
-rw-r--r--compiler/GHC/Tc/Solver/Monad.hs4
-rw-r--r--compiler/GHC/Tc/TyCl.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/Instance.hs2
-rw-r--r--compiler/GHC/Tc/TyCl/Utils.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Unify.hs2
-rw-r--r--compiler/GHC/Tc/Utils/Zonk.hs2
-rw-r--r--compiler/GHC/Types/Basic.hs2
-rw-r--r--compiler/GHC/Types/Demand.hs2
-rw-r--r--compiler/GHC/Types/Name/Occurrence.hs2
-rw-r--r--compiler/GHC/Utils/Misc.hs2
-rw-r--r--compiler/Language/Haskell/Syntax/Decls.hs2
-rw-r--r--compiler/Language/Haskell/Syntax/Expr.hs2
-rw-r--r--docs/users_guide/9.0.1-notes.rst2
-rw-r--r--docs/users_guide/9.2.1-notes.rst4
-rw-r--r--docs/users_guide/phases.rst2
-rw-r--r--docs/users_guide/using-optimisation.rst4
-rw-r--r--ghc/GHCi/UI.hs2
-rw-r--r--hadrian/src/Rules/Compile.hs2
-rw-r--r--includes/rts/FileLock.h2
-rw-r--r--libraries/base/Data/Traversable.hs2
-rw-r--r--libraries/base/GHC/Event/Windows.hsc2
-rw-r--r--libraries/base/GHC/ForeignPtr.hs2
-rw-r--r--libraries/base/GHC/IO/Windows/Encoding.hs2
-rw-r--r--libraries/base/GHC/IO/Windows/Handle.hsc2
-rw-r--r--libraries/base/Unsafe/Coerce.hs4
-rw-r--r--libraries/base/tests/perf/Makefile2
-rw-r--r--libraries/base/tests/perf/T17752.hs2
-rw-r--r--libraries/ghc-bignum/src/GHC/Num/Integer.hs2
-rw-r--r--rts/HeapStackCheck.cmm2
-rw-r--r--rts/RtsAPI.c4
-rw-r--r--rts/RtsFlags.c2
-rw-r--r--rts/Stats.c2
-rw-r--r--rts/sm/GC.c2
-rw-r--r--rts/win32/AsyncWinIO.c6
-rw-r--r--testsuite/driver/perf_notes.py2
-rw-r--r--testsuite/driver/testglobals.py2
-rw-r--r--testsuite/tests/codeGen/should_run/cgrun069_cmm.cmm2
-rw-r--r--testsuite/tests/dynlibs/all.T2
-rw-r--r--testsuite/tests/gadt/SynDataRec.hs2
-rw-r--r--testsuite/tests/hiefile/should_compile/Scopes.hs4
-rw-r--r--testsuite/tests/indexed-types/should_compile/T18809.hs2
-rw-r--r--testsuite/tests/linear/should_compile/CSETest.hs2
-rw-r--r--testsuite/tests/pmcheck/should_compile/T17340.hs2
-rw-r--r--testsuite/tests/pmcheck/should_compile/T18478.hs6
-rw-r--r--testsuite/tests/stranal/should_run/T13380d.hs2
-rw-r--r--testsuite/tests/stranal/should_run/T13380e.hs2
-rw-r--r--testsuite/tests/stranal/sigs/T18086.hs2
-rw-r--r--testsuite/tests/typecheck/should_fail/T17173.hs2
-rw-r--r--testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs2
85 files changed, 113 insertions, 113 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs
index 5d8b295b95..eef40f6c2b 100644
--- a/compiler/GHC.hs
+++ b/compiler/GHC.hs
@@ -857,7 +857,7 @@ looks_like_an_input m = isSourceFilename m
-- away. Note the asymmetry of FilePath.normalise:
-- Linux: p\/q -> p\/q; p\\q -> p\\q
-- Windows: p\/q -> p\\q; p\\q -> p\\q
--- #12674: Filenames starting with a hypen get normalised from ./-foo.hs
+-- #12674: Filenames starting with a hyphen get normalised from ./-foo.hs
-- to -foo.hs. We have to re-prepend the current directory.
normalise_hyp :: FilePath -> FilePath
normalise_hyp fp
diff --git a/compiler/GHC/Builtin/PrimOps.hs b/compiler/GHC/Builtin/PrimOps.hs
index 4ad8652922..14040692bc 100644
--- a/compiler/GHC/Builtin/PrimOps.hs
+++ b/compiler/GHC/Builtin/PrimOps.hs
@@ -634,7 +634,7 @@ Note [Eta expanding primops]
STG requires that primop applications be saturated. This makes code generation
significantly simpler since otherwise we would need to define a calling
-convention for curried applications that can accomodate levity polymorphism.
+convention for curried applications that can accommodate levity polymorphism.
To ensure saturation, CorePrep eta expands expand all primop applications as
described in Note [Eta expansion of hasNoBinding things in CorePrep] in
diff --git a/compiler/GHC/Cmm/CLabel.hs b/compiler/GHC/Cmm/CLabel.hs
index 75559edd2e..4b30bc8cf1 100644
--- a/compiler/GHC/Cmm/CLabel.hs
+++ b/compiler/GHC/Cmm/CLabel.hs
@@ -1378,7 +1378,7 @@ pprCLabel platform sty lbl =
-- Note that these labels are *not* referred to by code. They are strictly for
-- diagnostics purposes.
--
--- To avoid confusion, it is desireable to add a module-qualifier to the
+-- To avoid confusion, it is desirable to add a module-qualifier to the
-- symbol name. However, the Name type's Internal constructor doesn't carry
-- knowledge of the current Module. Consequently, we have to pass this around
-- explicitly.
diff --git a/compiler/GHC/Cmm/Info/Build.hs b/compiler/GHC/Cmm/Info/Build.hs
index b43eaa1257..1d3431c4af 100644
--- a/compiler/GHC/Cmm/Info/Build.hs
+++ b/compiler/GHC/Cmm/Info/Build.hs
@@ -441,7 +441,7 @@ counters are not exported. So we ignore ticky counters in SRT analysis (which
are never CAFFY and never exported).
Not doing this caused #17947 where we analysed the function first mapped the
-name to CAFFY. We then saw the ticky constructor, and becuase it has the same
+name to CAFFY. We then saw the ticky constructor, and because it has the same
Name as the function and is not CAFFY we overrode the CafInfo of the name as
non-CAFFY.
-}
diff --git a/compiler/GHC/CmmToAsm/BlockLayout.hs b/compiler/GHC/CmmToAsm/BlockLayout.hs
index b7c6ffb098..d7314eaa5b 100644
--- a/compiler/GHC/CmmToAsm/BlockLayout.hs
+++ b/compiler/GHC/CmmToAsm/BlockLayout.hs
@@ -539,7 +539,7 @@ mergeChains edges chains
-- An Edge is irrelevant if the ends are part of the same chain.
-- We say these edges are already linked
buildChains :: [CfgEdge] -> [BlockId]
- -> ( LabelMap BlockChain -- Resulting chains, indexd by end if chain.
+ -> ( LabelMap BlockChain -- Resulting chains, indexed by end if chain.
, Set.Set (BlockId, BlockId)) --List of fused edges.
buildChains edges blocks
= runST $ buildNext setEmpty mapEmpty mapEmpty edges Set.empty
diff --git a/compiler/GHC/CmmToAsm/Reg/Graph/Base.hs b/compiler/GHC/CmmToAsm/Reg/Graph/Base.hs
index a06934c837..32b49a61e8 100644
--- a/compiler/GHC/CmmToAsm/Reg/Graph/Base.hs
+++ b/compiler/GHC/CmmToAsm/Reg/Graph/Base.hs
@@ -141,7 +141,7 @@ bound regsOfClass regAlias classN classesC
-- | The total squeese on a particular node with a list of neighbors.
--
-- A version of this should be constructed for each particular architecture,
--- possibly including uses of bound, so that alised registers don't get
+-- possibly including uses of bound, so that aliased registers don't get
-- counted twice, as per the paper.
squeese :: (RegClass -> UniqSet Reg)
-> (Reg -> UniqSet Reg)
diff --git a/compiler/GHC/CmmToAsm/X86/CodeGen.hs b/compiler/GHC/CmmToAsm/X86/CodeGen.hs
index 3883d44717..36b24e8be2 100644
--- a/compiler/GHC/CmmToAsm/X86/CodeGen.hs
+++ b/compiler/GHC/CmmToAsm/X86/CodeGen.hs
@@ -3054,7 +3054,7 @@ genCCall32' target dest_regs args = do
X87Store fmt tmp_amode,
-- X87Store only supported for the CDECL ABI
-- NB: This code will need to be
- -- revisted once GHC does more work around
+ -- revisited once GHC does more work around
-- SIGFPE f
MOV fmt (OpAddr tmp_amode) (OpReg r_dest),
ADD II32 (OpImm (ImmInt b)) (OpReg esp),
diff --git a/compiler/GHC/Core/Lint.hs b/compiler/GHC/Core/Lint.hs
index f014a20817..f1720725a6 100644
--- a/compiler/GHC/Core/Lint.hs
+++ b/compiler/GHC/Core/Lint.hs
@@ -212,14 +212,14 @@ in GHC.Core.Opt.WorkWrap.Utils. (Maybe there are other "clients" of this featur
* Alas, when cloning a coercion variable we might choose a unique
that happens to clash with an inner Id, thus
\cv_66 -> let wild_X7 = blah in blah
- We decide to clone `cv_66` becuase it's already in scope. Fine,
+ We decide to clone `cv_66` because it's already in scope. Fine,
choose a new unique. Aha, X7 looks good. So we check the lambda
body with le_subst of [cv_66 :-> cv_X7]
This is all fine, even though we use the same unique as wild_X7.
As (SI2) says, we do /not/ return a new lambda
(\cv_X7 -> let wild_X7 = blah in ...)
- We simply use the le_subst subsitution in types/coercions only, when
+ We simply use the le_subst substitution in types/coercions only, when
checking for equality.
* We still need to check that Id occurrences are bound by some
diff --git a/compiler/GHC/Core/Opt/Arity.hs b/compiler/GHC/Core/Opt/Arity.hs
index 99cfd1b15f..6dd1148e56 100644
--- a/compiler/GHC/Core/Opt/Arity.hs
+++ b/compiler/GHC/Core/Opt/Arity.hs
@@ -682,7 +682,7 @@ This example happens a lot; it first showed up in Andy Gill's thesis,
fifteen years ago! It also shows up in the code for 'rnf' on lists
in #4138.
-We do the neccessary, quite simple fixed-point iteration in 'findRhsArity',
+We do the necessary, quite simple fixed-point iteration in 'findRhsArity',
which assumes for a single binding 'ABot' on the first run and iterates
until it finds a stable arity type. Two wrinkles
@@ -1339,7 +1339,7 @@ a (\eta) around the outside and use etaInfoApp to apply each
alternative to 'eta'. We want to beta-reduce all that junk
away.
-#18223 was a dramtic example in which the intermediate term was
+#18223 was a dramatic example in which the intermediate term was
grotesquely huge, even though the next Simplifier iteration squashed
it. Better to kill it at birth.
-}
diff --git a/compiler/GHC/Core/Opt/DmdAnal.hs b/compiler/GHC/Core/Opt/DmdAnal.hs
index 3eb86852ac..413da0794a 100644
--- a/compiler/GHC/Core/Opt/DmdAnal.hs
+++ b/compiler/GHC/Core/Opt/DmdAnal.hs
@@ -177,7 +177,7 @@ That is, a series of right-nested pairs, where the @fst@ are the exported
binders of the last enclosing let binding and @snd@ continues the nested
lets.
-Variables occuring free in RULE RHSs are to be handled the same as exported Ids.
+Variables occurring free in RULE RHSs are to be handled the same as exported Ids.
See also Note [Absence analysis for stable unfoldings and RULES].
Note [Why care for top-level demand annotations?]
@@ -204,7 +204,7 @@ to unbox deeper. From T18894:
h m = ... snd (g m 2) ... uncurry (+) (g 2 m) ...
Only @h@ is exported, hence we see that @g@ is always called in contexts were we
also force the division in the second component of the pair returned by @g@.
-This allows Nested CPR to evalute the division eagerly and return an I# in its
+This allows Nested CPR to evaluate the division eagerly and return an I# in its
position.
-}
@@ -1181,7 +1181,7 @@ For (2) consider
f _ (MkT n t) = f n t
Here f is lazy in T, but its *usage* is infinite: U(U,U(U,U(U, ...))).
-Notice that this happens becuase T is a product type, and is recrusive.
+Notice that this happens because T is a product type, and is recrusive.
If we are not careful, we'll fail to iterate to a fixpoint in dmdFix,
and bale out entirely, which is inefficient and over-conservative.
diff --git a/compiler/GHC/Core/Opt/OccurAnal.hs b/compiler/GHC/Core/Opt/OccurAnal.hs
index 343ddfe618..c5c5e4207a 100644
--- a/compiler/GHC/Core/Opt/OccurAnal.hs
+++ b/compiler/GHC/Core/Opt/OccurAnal.hs
@@ -302,7 +302,7 @@ in Note [IMP-RULES: local rules for imported functions].
So, during loop-breaker analysis:
-- for each active RULE for a local function 'f' we add an edge bewteen
+- for each active RULE for a local function 'f' we add an edge between
'f' and the local FVs of the rule RHS
- for each active RULE for an *imported* function we add dependency
@@ -639,7 +639,7 @@ propagate.
{-# RULES "SPEC k 0" k 0 = j #-}
k x y = x + 2 * y
in ...
- If we eta-expanded the rule all woudl be well, but as it stands the
+ If we eta-expanded the rule all would be well, but as it stands the
one arg of the rule don't match the join-point arity of 2.
Conceivably we could notice that a potential join point would have
diff --git a/compiler/GHC/Core/Opt/Simplify.hs b/compiler/GHC/Core/Opt/Simplify.hs
index 97173eee5c..0cea6da0bf 100644
--- a/compiler/GHC/Core/Opt/Simplify.hs
+++ b/compiler/GHC/Core/Opt/Simplify.hs
@@ -3653,7 +3653,7 @@ Pushing the call inward (being careful not to duplicate E)
and now the (&& a F) etc can optimise. Moreover there might
be a RULE for the function that can fire when it "sees" the
-particular case alterantive.
+particular case alternative.
But Plan A can have terrible, terrible behaviour. Here is a classic
case:
diff --git a/compiler/GHC/Core/Opt/Simplify/Utils.hs b/compiler/GHC/Core/Opt/Simplify/Utils.hs
index 2ab7fe2e28..191e72e3b2 100644
--- a/compiler/GHC/Core/Opt/Simplify/Utils.hs
+++ b/compiler/GHC/Core/Opt/Simplify/Utils.hs
@@ -1479,7 +1479,7 @@ different way (Note [Duplicating StrictArg] in Simplify).
So I just set an arbitrary, high limit of 100, to stop any
totally exponential behaviour.
-This still leaves the nasty possiblity that /ordinary/ inlining (not
+This still leaves the nasty possibility that /ordinary/ inlining (not
postInlineUnconditionally) might inline these join points, each of
which is individually quiet small. I'm still not sure what to do
about this (e.g. see #15488).
diff --git a/compiler/GHC/Core/Opt/Specialise.hs b/compiler/GHC/Core/Opt/Specialise.hs
index 4ff730fa77..c2510b97c0 100644
--- a/compiler/GHC/Core/Opt/Specialise.hs
+++ b/compiler/GHC/Core/Opt/Specialise.hs
@@ -867,7 +867,7 @@ call to spec_imorpts in spec_import, we must include the dict-binds
from the parent. Lacking this caused #17151, a really nasty bug.
Here is what happened.
-* Class struture:
+* Class structure:
Source is a superclass of Mut
Index is a superclass of Source
diff --git a/compiler/GHC/Core/TyCo/FVs.hs b/compiler/GHC/Core/TyCo/FVs.hs
index 8277b06378..c8a7506363 100644
--- a/compiler/GHC/Core/TyCo/FVs.hs
+++ b/compiler/GHC/Core/TyCo/FVs.hs
@@ -383,7 +383,7 @@ shallowTcvFolder = TyCoFolder { tcf_view = noView
{- Note [Finding free coercion varibles]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Here we are only interested in the free /coercion/ variables.
-We can achieve this through a slightly differnet TyCo folder.
+We can achieve this through a slightly different TyCo folder.
Notice that we look deeply, into kinds.
diff --git a/compiler/GHC/Core/TyCo/Rep.hs b/compiler/GHC/Core/TyCo/Rep.hs
index 69db14e7f0..7414bc18da 100644
--- a/compiler/GHC/Core/TyCo/Rep.hs
+++ b/compiler/GHC/Core/TyCo/Rep.hs
@@ -1909,7 +1909,7 @@ foldTyCo (TyCoFolder { tcf_view = view
= let !env' = tycobinder env tv vis -- Avoid building a thunk here
in go_ty env (varType tv) `mappend` go_ty env' inner
- -- Explicit recursion becuase using foldr builds a local
+ -- Explicit recursion because using foldr builds a local
-- loop (with env free) and I'm not confident it'll be
-- lambda lifted in the end
go_tys _ [] = mempty
diff --git a/compiler/GHC/Core/Type.hs b/compiler/GHC/Core/Type.hs
index 21f03d653e..7032b97939 100644
--- a/compiler/GHC/Core/Type.hs
+++ b/compiler/GHC/Core/Type.hs
@@ -1158,7 +1158,7 @@ is equivalent to,
FunTy (Anon a) b
Note how the RuntimeReps are implied in the FunTy representation. For this
-reason we must be careful when recontructing the TyConApp representation (see,
+reason we must be careful when reconstructing the TyConApp representation (see,
for instance, splitTyConApp_maybe).
In the compiler we maintain the invariant that all saturated applications of
diff --git a/compiler/GHC/Core/Unfold.hs b/compiler/GHC/Core/Unfold.hs
index 0d0df57f57..b97e10cd46 100644
--- a/compiler/GHC/Core/Unfold.hs
+++ b/compiler/GHC/Core/Unfold.hs
@@ -810,7 +810,7 @@ binary sizes shrink significantly either.
Note [Discounts and thresholds]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Constants for discounts and thesholds are defined in 'UnfoldingOpts'. They are:
+Constants for discounts and thresholds are defined in 'UnfoldingOpts'. They are:
unfoldingCreationThreshold
At a definition site, if the unfolding is bigger than this, we
diff --git a/compiler/GHC/Core/Unify.hs b/compiler/GHC/Core/Unify.hs
index 81492afc86..dbfd4083ad 100644
--- a/compiler/GHC/Core/Unify.hs
+++ b/compiler/GHC/Core/Unify.hs
@@ -529,7 +529,7 @@ instance Monad UnifyResultM where
SurelyApart -> SurelyApart
Unifiable x >>= f = f x
--- | @tcUnifyTysFG bind_tv tys1 tys2@ attepts to find a substitution @s@ (whose
+-- | @tcUnifyTysFG bind_tv tys1 tys2@ attempts to find a substitution @s@ (whose
-- domain elements all respond 'BindMe' to @bind_tv@) such that
-- @s(tys1)@ and that of @s(tys2)@ are equal, as witnessed by the returned
-- Coercions. This version requires that the kinds of the types are the same,
diff --git a/compiler/GHC/CoreToStg/Prep.hs b/compiler/GHC/CoreToStg/Prep.hs
index 626fcadfce..9eae6867ac 100644
--- a/compiler/GHC/CoreToStg/Prep.hs
+++ b/compiler/GHC/CoreToStg/Prep.hs
@@ -1028,7 +1028,7 @@ Performing the transform described above would result in:
If runRW# were a "normal" function this call to join point j would not be
allowed in its continuation argument. However, since runRW# is inlined (as
-described in Note [runRW magic] above), such join point occurences are
+described in Note [runRW magic] above), such join point occurrences are
completely fine. Both occurrence analysis (see the runRW guard in occAnalApp)
and Core Lint (see the App case of lintCoreExpr) have special treatment for
runRW# applications. See Note [Linting of runRW#] for details on the latter.
diff --git a/compiler/GHC/HsToCore/Expr.hs b/compiler/GHC/HsToCore/Expr.hs
index 259615e64c..d2c5d77cbe 100644
--- a/compiler/GHC/HsToCore/Expr.hs
+++ b/compiler/GHC/HsToCore/Expr.hs
@@ -240,7 +240,7 @@ dsUnliftedBind bind body = pprPanic "dsLet: unlifted" (ppr bind $$ ppr body)
-}
--- | Replace the body of the fucntion with this block to test the hsExprType
+-- | Replace the body of the function with this block to test the hsExprType
-- function in GHC.Tc.Utils.Zonk:
-- putSrcSpanDs loc $ do
-- { core_expr <- dsExpr e
@@ -682,7 +682,7 @@ We have
MkF (co2::s ~# Int) _ -> $WMkF @t y |> co3
(Side note: here (z |> co1) is built by typechecking the scrutinee, so
-we ignore it here. In general the scrutinee is an aribtrary expression.)
+we ignore it here. In general the scrutinee is an arbitrary expression.)
The question is: what is co3, the cast for the RHS?
co3 :: F (Int,t) ~ F (s,t)
diff --git a/compiler/GHC/Iface/UpdateIdInfos.hs b/compiler/GHC/Iface/UpdateIdInfos.hs
index e37964c51d..0c70b5caeb 100644
--- a/compiler/GHC/Iface/UpdateIdInfos.hs
+++ b/compiler/GHC/Iface/UpdateIdInfos.hs
@@ -27,7 +27,7 @@ import GHC.Utils.Panic
#include "HsVersions.h"
--- | Update CafInfos and LFInfos of all occurences (in rules, unfoldings, class
+-- | Update CafInfos and LFInfos of all occurrences (in rules, unfoldings, class
-- instances).
--
-- See Note [Conveying CAF-info and LFInfo between modules] in
diff --git a/compiler/GHC/Linker/MacOS.hs b/compiler/GHC/Linker/MacOS.hs
index 959ef3a217..be5cbf2f9c 100644
--- a/compiler/GHC/Linker/MacOS.hs
+++ b/compiler/GHC/Linker/MacOS.hs
@@ -36,7 +36,7 @@ import System.FilePath ((</>), (<.>))
-- @-l@ and @-rpath@ to the linker will result in the unnecesasry libraries not
-- being included in the load commands, however the @-rpath@ entries are all
-- forced to be included. This can lead to 100s of @-rpath@ entries being
--- included when only a handful of libraries end up being truely linked.
+-- included when only a handful of libraries end up being truly linked.
--
-- Thus after building the library, we run a fixup phase where we inject the
-- @-rpath@ for each found library (in the given library search paths) into the
diff --git a/compiler/GHC/Parser/Errors.hs b/compiler/GHC/Parser/Errors.hs
index 57c6141117..f0f4372c8a 100644
--- a/compiler/GHC/Parser/Errors.hs
+++ b/compiler/GHC/Parser/Errors.hs
@@ -36,8 +36,8 @@ data PsWarning
-- | Warn when tabulations are found
= PsWarnTab
- { tabFirst :: !SrcSpan -- ^ First occurence of a tab
- , tabCount :: !Word -- ^ Number of other occurences
+ { tabFirst :: !SrcSpan -- ^ First occurrence of a tab
+ , tabCount :: !Word -- ^ Number of other occurrences
}
| PsWarnTransitionalLayout !SrcSpan !TransLayoutReason
@@ -53,7 +53,7 @@ data PsWarning
-- ^ Multiple Haddock comment for the same entity
| PsWarnStarBinder !SrcSpan
- -- ^ Found binding occurence of "*" while StarIsType is enabled
+ -- ^ Found binding occurrence of "*" while StarIsType is enabled
| PsWarnStarIsType !SrcSpan
-- ^ Using "*" for "Type" without StarIsType enabled
@@ -103,7 +103,7 @@ data PsErrorDesc
-- ^ Lexer error
| PsErrSuffixAT
- -- ^ Suffix occurence of `@`
+ -- ^ Suffix occurrence of `@`
| PsErrParse !String
-- ^ Parse errors
diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x
index aaae9077b6..5e2af15f96 100644
--- a/compiler/GHC/Parser/Lexer.x
+++ b/compiler/GHC/Parser/Lexer.x
@@ -2849,7 +2849,7 @@ getMessages :: PState -> (Bag PsWarning, Bag PsError)
getMessages p =
let ws = warnings p
-- we add the tabulation warning on the fly because
- -- we count the number of occurences of tab characters
+ -- we count the number of occurrences of tab characters
ws' = case tab_first p of
Nothing -> ws
Just tf -> PsWarnTab (RealSrcSpan tf Nothing) (tab_count p)
diff --git a/compiler/GHC/Parser/PostProcess/Haddock.hs b/compiler/GHC/Parser/PostProcess/Haddock.hs
index 6741476925..43ac07a482 100644
--- a/compiler/GHC/Parser/PostProcess/Haddock.hs
+++ b/compiler/GHC/Parser/PostProcess/Haddock.hs
@@ -110,7 +110,7 @@ the location range in which we search for HdkCommentPrev is as follows:
We search for comments after HsTyVar "Int" and until the next syntactic
element, in this case HsTyVar "Bool".
-Ignoring the "->" allows us to accomodate alternative coding styles:
+Ignoring the "->" allows us to accommodate alternative coding styles:
f :: Int -> -- ^ comment on argument
Bool -- ^ comment on result
@@ -1540,7 +1540,7 @@ Sometimes handling documentation comments during parsing led to bugs (#17561),
and sometimes it simply made it hard to modify and extend the grammar.
Another issue was that sometimes Haddock would fail to parse code
-that GHC could parse succesfully:
+that GHC could parse successfully:
class BadIndent where
f :: a -> Int
diff --git a/compiler/GHC/Rename/Env.hs b/compiler/GHC/Rename/Env.hs
index 6e0c19f190..19c4e4610e 100644
--- a/compiler/GHC/Rename/Env.hs
+++ b/compiler/GHC/Rename/Env.hs
@@ -1112,7 +1112,7 @@ lookupGlobalOccRn rdr_name =
Nothing -> do { traceRn "lookupGlobalOccRn" (ppr rdr_name)
; unboundName WL_Global rdr_name }
--- Looks up a RdrName occurence in the GlobalRdrEnv and with
+-- Looks up a RdrName occurrence in the GlobalRdrEnv and with
-- lookupQualifiedNameGHCi. Does not try to find an Exact or Orig name first.
-- lookupQualifiedNameGHCi here is used when we're in GHCi and a name like
-- 'Data.Map.elems' is typed, even if you didn't import Data.Map
diff --git a/compiler/GHC/Runtime/Interpreter.hs b/compiler/GHC/Runtime/Interpreter.hs
index 4536226bf8..cb13089571 100644
--- a/compiler/GHC/Runtime/Interpreter.hs
+++ b/compiler/GHC/Runtime/Interpreter.hs
@@ -202,7 +202,7 @@ iservCmd hsc_env msg = withInterp hsc_env $ \case
withInterp :: HscEnv -> (Interp -> IO a) -> IO a
withInterp hsc_env action = action (hscInterp hsc_env)
--- | Retreive the targe code interpreter
+-- | Retrieve the targe code interpreter
--
-- Fails if no target code interpreter is available
hscInterp :: HscEnv -> Interp
diff --git a/compiler/GHC/StgToCmm/Foreign.hs b/compiler/GHC/StgToCmm/Foreign.hs
index 9bae125ce5..21c85d569c 100644
--- a/compiler/GHC/StgToCmm/Foreign.hs
+++ b/compiler/GHC/StgToCmm/Foreign.hs
@@ -460,7 +460,7 @@ Opening the nursery corresponds to the following code:
tso->alloc_limit += bdfree - bdstart;
// Set Hp to the last occupied word of the heap block. Why not the
- // next unocupied word? Doing it this way means that we get to use
+ // next unoccupied word? Doing it this way means that we get to use
// an offset of zero more often, which might lead to slightly smaller
// code on some architectures.
Hp = bdfree - WDS(1);
diff --git a/compiler/GHC/Tc/Deriv/Generate.hs b/compiler/GHC/Tc/Deriv/Generate.hs
index 2bda9d40c6..0f374700dd 100644
--- a/compiler/GHC/Tc/Deriv/Generate.hs
+++ b/compiler/GHC/Tc/Deriv/Generate.hs
@@ -2682,7 +2682,7 @@ avoid name clashes:
toEnum a = $tag2con_T{Uniq2} a
-- $tag2con_T{Uniq1} and $tag2con_T{Uniq2} are Exact RdrNames with
- -- underyling System Names
+ -- underlying System Names
$tag2con_T{Uniq1} :: Int -> T
$tag2con_T{Uniq1} = ...code....
diff --git a/compiler/GHC/Tc/Gen/App.hs b/compiler/GHC/Tc/Gen/App.hs
index 83f8cc567d..5b34952d65 100644
--- a/compiler/GHC/Tc/Gen/App.hs
+++ b/compiler/GHC/Tc/Gen/App.hs
@@ -291,7 +291,7 @@ tcApp rn_expr exp_res_ty
-- Zonk the result type, to ensure that we substitute out
-- any filled-in instantiation variable before calling tcWrapResultMono
- -- In the Check case, this isn't really necessary, becuase tcWrapResultMono
+ -- In the Check case, this isn't really necessary, because tcWrapResultMono
-- just drops to tcUnify; but in the Infer case a filled-in instantiation
-- variable might perhaps escape into the constraint generator. The safe
-- thing to do is to any instantaition variables away.
@@ -318,7 +318,7 @@ wantQuickLook _ = xoptM LangExt.Impredi
zonkQuickLook :: Bool -> TcType -> TcM TcType
-- After all Quick Look unifications are done, zonk to ensure that all
--- instantation variables are substituted away
+-- instantiation variables are substituted away
--
-- So far as the paper is concerned, this step applies
-- the poly-substitution Theta, learned by QL, so that we
@@ -677,7 +677,7 @@ over any visible type arguments. We've already inferred the type of
the function (in tcInferAppHead), so we'll /already/ have emitted a
Hole constraint; failing preserves that constraint.
-We do /not/ want to fail altogether in this case (via failM) becuase
+We do /not/ want to fail altogether in this case (via failM) because
that may abandon an entire instance decl, which (in the presence of
-fdefer-type-errors) leads to leading to #17792.
diff --git a/compiler/GHC/Tc/Gen/Bind.hs b/compiler/GHC/Tc/Gen/Bind.hs
index c677643be5..c63cbabdc1 100644
--- a/compiler/GHC/Tc/Gen/Bind.hs
+++ b/compiler/GHC/Tc/Gen/Bind.hs
@@ -632,7 +632,7 @@ tcPolyCheck prag_fn
(mkCheckExpType rho_ty)
-- We make a funny AbsBinds, abstracting over nothing,
- -- just so we haev somewhere to put the SpecPrags.
+ -- just so we have somewhere to put the SpecPrags.
-- Otherwise we could just use the FunBind
-- Hence poly_id2 is just a clone of poly_id;
-- We re-use mono-name, but we could equally well use a fresh one
diff --git a/compiler/GHC/Tc/Gen/HsType.hs b/compiler/GHC/Tc/Gen/HsType.hs
index 698f81185d..87da41b890 100644
--- a/compiler/GHC/Tc/Gen/HsType.hs
+++ b/compiler/GHC/Tc/Gen/HsType.hs
@@ -473,7 +473,7 @@ tc_lhs_sig_type skol_info (L loc (HsSig { sig_bndrs = hs_outer_bndrs
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
tcHsSigType is tricky. Consider (T11142)
foo :: forall b. (forall k (a :: k). SameKind a b) -> ()
-This is ill-kinded becuase of a nested skolem-escape.
+This is ill-kinded because of a nested skolem-escape.
That will show up as an un-solvable constraint in the implication
returned by buildTvImplication in tc_lhs_sig_type. See Note [Skolem
@@ -3249,7 +3249,7 @@ bindImplicitTKBndrsX skol_mode@(SM { sm_parent = check_parent, sm_kind = ctxt_ki
-- SkolemMode
--------------------------------------
--- | 'SkolemMode' decribes how to typecheck an explicit ('HsTyVarBndr') or
+-- | 'SkolemMode' describes how to typecheck an explicit ('HsTyVarBndr') or
-- implicit ('Name') binder in a type. It is just a record of flags
-- that describe what sort of 'TcTyVar' to create.
data SkolemMode
@@ -3430,7 +3430,7 @@ filterConstrainedCandidates wanted dvs
; _ <- promoteTyVarSet to_promote
; return dvs' }
--- |- Specialised verison of 'kindGeneralizeSome', but with empty
+-- |- Specialised version of 'kindGeneralizeSome', but with empty
-- WantedConstraints, so no filtering is needed
-- i.e. kindGeneraliseAll = kindGeneralizeSome emptyWC
kindGeneralizeAll :: TcType -> TcM [KindVar]
@@ -3440,7 +3440,7 @@ kindGeneralizeAll kind_or_type
; quantifyTyVars dvs }
-- | Specialized version of 'kindGeneralizeSome', but where no variables
--- can be generalized, but perhaps some may neeed to be promoted.
+-- can be generalized, but perhaps some may need to be promoted.
-- Use this variant when it is unknowable whether metavariables might
-- later be constrained.
--
@@ -3911,7 +3911,7 @@ We achieve this as follows:
- For /named/ wildcards such sas
g :: forall b. (forall la. a -> _x) -> b
there is no problem: we create them at the outer level (ie the
- ambient level of teh signature itself), and push the level when we
+ ambient level of the signature itself), and push the level when we
go inside a forall. So now the unification variable for the "_x"
can't unify with skolem 'a'.
diff --git a/compiler/GHC/Tc/Gen/Pat.hs b/compiler/GHC/Tc/Gen/Pat.hs
index 442d287ed8..837fb7fbdc 100644
--- a/compiler/GHC/Tc/Gen/Pat.hs
+++ b/compiler/GHC/Tc/Gen/Pat.hs
@@ -458,7 +458,7 @@ Consider this exotic example:
f :: Int -> blah
f (pair True -> x) = ...here (x :: forall b. b -> (Int,b))
-The expresion (pair True) should have type
+The expression (pair True) should have type
pair True :: Int -> forall b. b -> (Int,b)
so that it is ready to consume the incoming Int. It should be an
arrow type (t1 -> t2); hence using (tcInferRho expr).
diff --git a/compiler/GHC/Tc/Solver.hs b/compiler/GHC/Tc/Solver.hs
index 7e1f919e1f..697cea0f47 100644
--- a/compiler/GHC/Tc/Solver.hs
+++ b/compiler/GHC/Tc/Solver.hs
@@ -223,7 +223,7 @@ simplifyAndEmitFlatConstraints wanted
; tclvl <- TcM.getTcLevel
; implic <- buildTvImplication UnkSkol [] tclvl wanted
-- UnkSkol: doesn't matter, because
- -- we bind no skolem varaibles here
+ -- we bind no skolem variables here
; emitImplication implic
; failM }
Just (simples, holes)
@@ -312,7 +312,7 @@ should be well. BUT it's hard to see that when kind-checking the signature
for undefined. We want to emit a residual (a~b) constraint, to solve
later.
-Another possiblity is that we might have something like
+Another possibility is that we might have something like
F alpha ~ [Int]
where alpha is bound further out, which might become soluble
"later" when we learn more about alpha. So we want to emit
diff --git a/compiler/GHC/Tc/Solver/Interact.hs b/compiler/GHC/Tc/Solver/Interact.hs
index b1eb5bd712..00ee528fdc 100644
--- a/compiler/GHC/Tc/Solver/Interact.hs
+++ b/compiler/GHC/Tc/Solver/Interact.hs
@@ -1577,7 +1577,7 @@ by unification, there are two cases to consider
alpha[n] is at level n, and so if we set, say,
alpha[n] := Maybe beta[m],
we must ensure that when unifying beta we do skolem-escape checks
- etc relevent to level n. Simple way to do that: promote beta to
+ etc relevant to level n. Simple way to do that: promote beta to
level n.
2. Set the Unification Level Flag to record that a level-n unification has
@@ -1586,7 +1586,7 @@ by unification, there are two cases to consider
NB: UnifySameLevel is just an optimisation for UnifyOuterLevel. Promotion
would be a no-op, and setting the unification flag unnecessarily would just
make the solver iterate more often. (We don't need to iterate when unifying
-at the ambient level becuase of the kick-out mechanism.)
+at the ambient level because of the kick-out mechanism.)
************************************************************************
diff --git a/compiler/GHC/Tc/Solver/Monad.hs b/compiler/GHC/Tc/Solver/Monad.hs
index c5e9c343ae..4c16f2f56e 100644
--- a/compiler/GHC/Tc/Solver/Monad.hs
+++ b/compiler/GHC/Tc/Solver/Monad.hs
@@ -2040,7 +2040,7 @@ NB: we could in principle avoid kick-out:
b) For Givens, after a unification. By (GivenInv) in GHC.Tc.Utils.TcType
Note [TcLevel invariants], a Given can't include a meta-tyvar from
its own level, so it falls under (a). Of course, we must still
- kick out Givens when adding a new non-unificaiton Given.
+ kick out Givens when adding a new non-unification Given.
But kicking out more vigorously may lead to earlier unification and fewer
iterations, so we don't take advantage of these possibilities.
@@ -3438,7 +3438,7 @@ Answer: if any unification of a tyvar at level n takes place
* What if a unification takes place at level n, in the ic_simples of
level n? No need to track this, because the kick-out mechanism deals
- with it. (We can't drop kick-out in favour of iteration, becuase kick-out
+ with it. (We can't drop kick-out in favour of iteration, because kick-out
works for skolem-equalities, not just unifications.)
So the monad-global Unification Level Flag, kept in tcs_unif_lvl keeps
diff --git a/compiler/GHC/Tc/TyCl.hs b/compiler/GHC/Tc/TyCl.hs
index d434331605..6f7a7c548c 100644
--- a/compiler/GHC/Tc/TyCl.hs
+++ b/compiler/GHC/Tc/TyCl.hs
@@ -779,7 +779,7 @@ swizzleTcTyConBndrs tc_infos
| (tc, scoped_prs, kind) <- tc_infos ]
swizzle_prs :: [(Name,TyVar)]
- -- Pairs the user-specifed Name with its representative TyVar
+ -- Pairs the user-specified Name with its representative TyVar
-- See Note [Swizzling the tyvars before generaliseTcTyCon]
swizzle_prs = [ pr | (_, prs, _) <- tc_infos, pr <- prs ]
diff --git a/compiler/GHC/Tc/TyCl/Instance.hs b/compiler/GHC/Tc/TyCl/Instance.hs
index 8bc1d3a746..469ef20778 100644
--- a/compiler/GHC/Tc/TyCl/Instance.hs
+++ b/compiler/GHC/Tc/TyCl/Instance.hs
@@ -1112,7 +1112,7 @@ the /data constructor/ declarations altogether, looking only at the
data instance /header/.
Observations:
-* This choice is simple to describe, as well as simple to implment.
+* This choice is simple to describe, as well as simple to implement.
For a data/newtype instance decl, the instance kinds are influenced
/only/ by the header.
diff --git a/compiler/GHC/Tc/TyCl/Utils.hs b/compiler/GHC/Tc/TyCl/Utils.hs
index b9fb54cc9f..2135f18b77 100644
--- a/compiler/GHC/Tc/TyCl/Utils.hs
+++ b/compiler/GHC/Tc/TyCl/Utils.hs
@@ -1105,6 +1105,6 @@ We want to generate HsBinds for unT that look something like this:
Note that the type of recSelError is `forall r (a :: TYPE r). Addr# -> a`.
Therefore, when used in the right-hand side of `unT`, GHC attempts to
instantiate `a` with `(forall b. b -> b) -> Int`, which is impredicative.
-To make sure that GHC is OK with this, we enable ImpredicativeTypes interally
+To make sure that GHC is OK with this, we enable ImpredicativeTypes internally
when typechecking these HsBinds so that the user does not have to.
-}
diff --git a/compiler/GHC/Tc/Utils/Unify.hs b/compiler/GHC/Tc/Utils/Unify.hs
index 23dcfe6e83..121ebfbe7e 100644
--- a/compiler/GHC/Tc/Utils/Unify.hs
+++ b/compiler/GHC/Tc/Utils/Unify.hs
@@ -176,7 +176,7 @@ before looking for an arrow type.
But if it doesn't find an arrow type, it wants to generate a message
like "f is applied to two arguments but its type only has one".
-To do that, it needs to konw about the args that tcArgs has already
+To do that, it needs to know about the args that tcArgs has already
munched up -- hence passing in n_val_args_in_call and arg_tys_so_far;
and hence also the accumulating so_far arg to 'go'.
diff --git a/compiler/GHC/Tc/Utils/Zonk.hs b/compiler/GHC/Tc/Utils/Zonk.hs
index 76b101c679..4fb5286c70 100644
--- a/compiler/GHC/Tc/Utils/Zonk.hs
+++ b/compiler/GHC/Tc/Utils/Zonk.hs
@@ -1777,7 +1777,7 @@ Solution: (see #15552 for other variants)
the treatment of lexically-scoped variables in ze_tv_env and
ze_id_env.)
- Is the extra work worth it? Some non-sytematic perf measurements
+ Is the extra work worth it? Some non-systematic perf measurements
suggest that compiler allocation is reduced overall (by 0.5% or so)
but compile time really doesn't change.
-}
diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs
index 3b2f1a3140..4c92b8f9a3 100644
--- a/compiler/GHC/Types/Basic.hs
+++ b/compiler/GHC/Types/Basic.hs
@@ -938,7 +938,7 @@ type RulesOnly = Bool
type BranchCount = Int
-- For OneOcc, the BranchCount says how many syntactic occurrences there are
-- At the moment we really only check for 1 or >1, but in principle
- -- we could pay attention to how *many* occurences there are
+ -- we could pay attention to how *many* occurrences there are
-- (notably in postInlineUnconditionally).
-- But meanwhile, Ints are very efficiently represented.
diff --git a/compiler/GHC/Types/Demand.hs b/compiler/GHC/Types/Demand.hs
index c2e4770da6..0a23e10224 100644
--- a/compiler/GHC/Types/Demand.hs
+++ b/compiler/GHC/Types/Demand.hs
@@ -1300,7 +1300,7 @@ But the demand fed into f might be less than CS(CS(U)). Then we have to
- We have to multiply divergence with C_01. If r says that f Diverges for sure,
then this holds when the demand guarantees that two arguments are going to
be passed. If the demand is lower, we may just as well converge.
- If we were tracking definite convegence, than that would still hold under
+ If we were tracking definite convergence, than that would still hold under
a weaker demand than expected by the demand transformer.
* Used more than once, e.g. CM(CS(U)):
- Multiply with C_1N. Even if f puts a used-once demand on any of its argument
diff --git a/compiler/GHC/Types/Name/Occurrence.hs b/compiler/GHC/Types/Name/Occurrence.hs
index d2e4127010..d29d7ab7ec 100644
--- a/compiler/GHC/Types/Name/Occurrence.hs
+++ b/compiler/GHC/Types/Name/Occurrence.hs
@@ -646,7 +646,7 @@ mkNewTyCoOcc = mk_simple_deriv tcName "N:" -- Coercion for newtypes
mkInstTyCoOcc = mk_simple_deriv tcName "D:" -- Coercion for type functions
mkEqPredCoOcc = mk_simple_deriv tcName "$co"
--- Used in derived instances for the names of auxilary bindings.
+-- Used in derived instances for the names of auxiliary bindings.
-- See Note [Auxiliary binders] in GHC.Tc.Deriv.Generate.
mkCon2TagOcc = mk_simple_deriv varName "$con2tag_"
mkTag2ConOcc = mk_simple_deriv varName "$tag2con_"
diff --git a/compiler/GHC/Utils/Misc.hs b/compiler/GHC/Utils/Misc.hs
index d0989de39e..46fb352e61 100644
--- a/compiler/GHC/Utils/Misc.hs
+++ b/compiler/GHC/Utils/Misc.hs
@@ -785,7 +785,7 @@ splitAtList xs ys = go 0# xs ys
-- drop from the end of a list
dropTail :: Int -> [a] -> [a]
-- Specification: dropTail n = reverse . drop n . reverse
--- Better implemention due to Joachim Breitner
+-- Better implementation due to Joachim Breitner
-- http://www.joachim-breitner.de/blog/archives/600-On-taking-the-last-n-elements-of-a-list.html
dropTail n xs
= go (drop n xs) xs
diff --git a/compiler/Language/Haskell/Syntax/Decls.hs b/compiler/Language/Haskell/Syntax/Decls.hs
index ff65d085c7..453b963028 100644
--- a/compiler/Language/Haskell/Syntax/Decls.hs
+++ b/compiler/Language/Haskell/Syntax/Decls.hs
@@ -950,7 +950,7 @@ type LDerivClauseTys pass = XRec pass (DerivClauseTys pass)
-- | The types mentioned in a single @deriving@ clause. This can come in two
-- forms, 'DctSingle' or 'DctMulti', depending on whether the types are
-- surrounded by enclosing parentheses or not. These parentheses are
--- semantically differnt than 'HsParTy'. For example, @deriving ()@ means
+-- semantically different than 'HsParTy'. For example, @deriving ()@ means
-- \"derive zero classes\" rather than \"derive an instance of the 0-tuple\".
--
-- 'DerivClauseTys' use 'LHsSigType' because @deriving@ clauses can mention
diff --git a/compiler/Language/Haskell/Syntax/Expr.hs b/compiler/Language/Haskell/Syntax/Expr.hs
index 72c16fe22a..0e54adb8f4 100644
--- a/compiler/Language/Haskell/Syntax/Expr.hs
+++ b/compiler/Language/Haskell/Syntax/Expr.hs
@@ -1267,7 +1267,7 @@ data ParStmtBlock idL idR
-- | The fail operator
--
--- This is used for `.. <-` "bind statments" in do notation, including
+-- This is used for `.. <-` "bind statements" in do notation, including
-- non-monadic "binds" in applicative.
--
-- The fail operator is 'Just expr' if it potentially fail monadically. if the
diff --git a/docs/users_guide/9.0.1-notes.rst b/docs/users_guide/9.0.1-notes.rst
index 4b6ae89290..46c847191a 100644
--- a/docs/users_guide/9.0.1-notes.rst
+++ b/docs/users_guide/9.0.1-notes.rst
@@ -40,7 +40,7 @@ Highlights
GHC is now able to detect the case alt returning 3 as redundant.
- Some more performance improvements in edge cases.
-* Windows: Use the larg address space allocator.
+* Windows: Use the large address space allocator.
This improves runtime but causes increased memory usage on Windows versions
older than Win 8.1/Server 2012.
diff --git a/docs/users_guide/9.2.1-notes.rst b/docs/users_guide/9.2.1-notes.rst
index a51875d3f4..96306e4d9c 100644
--- a/docs/users_guide/9.2.1-notes.rst
+++ b/docs/users_guide/9.2.1-notes.rst
@@ -98,7 +98,7 @@ Runtime system
- The :rts-flag:`-h` flag has been deprecated, use either :rts-flag:`-hc` or
- :rts-flag:`-hT` explicitly, as appropiate.
+ :rts-flag:`-hT` explicitly, as appropriate.
``ghc-prim`` library
~~~~~~~~~~~~~~~~~~~~
@@ -163,7 +163,7 @@ Runtime system
``Natural``. As a consequence, one must enable ``TypeSynonymInstances``
in order to define instances for ``Nat``.
- The ``Numeric`` module recieves ``showBin`` and ``readBin`` to show and
+ The ``Numeric`` module receives ``showBin`` and ``readBin`` to show and
read integer numbers in binary.
- ``Char`` gets type-level support by analogy with strings and natural numbers.
diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst
index 797b10e8fe..73d9777f99 100644
--- a/docs/users_guide/phases.rst
+++ b/docs/users_guide/phases.rst
@@ -190,7 +190,7 @@ the following flags:
specified compiler will support it. This flag can be used to indicate
that ``-no-pie`` is supported. It has to be passed after ``-pgmc``.
- This flag is not neccessary when ``-pgmc`` is not used, since GHC
+ This flag is not necessary when ``-pgmc`` is not used, since GHC
remembers whether the default C compiler supports ``-no-pie`` in
an internal settings file.
diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst
index ee5b1de95e..a53fa21802 100644
--- a/docs/users_guide/using-optimisation.rst
+++ b/docs/users_guide/using-optimisation.rst
@@ -1147,8 +1147,8 @@ by saying ``-fno-wombat``.
dummy value at the call site or omitted altogether.
The worker/wrapper transformation (:ghc-flag:`-fworker-wrapper`) is
- reponsible for exploiting unboxing opportunities and replacing absent
- arguments by dummies. For arugments that can't be unboxed, opportunities
+ responsible for exploiting unboxing opportunities and replacing absent
+ arguments by dummies. For arguments that can't be unboxed, opportunities
for call-by-value and call-by-name are exploited in CorePrep when
translating to STG.
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs
index 77801019ee..48886ea88f 100644
--- a/ghc/GHCi/UI.hs
+++ b/ghc/GHCi/UI.hs
@@ -1838,7 +1838,7 @@ buildDocComponents str name = do
pure DocComponents{..}
--- | Produce output containing the type/kind signature, category, and definiton
+-- | Produce output containing the type/kind signature, category, and definition
-- location of a TyThing.
sigAndLocDoc :: String -> TyThing -> SDoc
sigAndLocDoc str tyThing =
diff --git a/hadrian/src/Rules/Compile.hs b/hadrian/src/Rules/Compile.hs
index 0efcea9474..b21bcaf74b 100644
--- a/hadrian/src/Rules/Compile.hs
+++ b/hadrian/src/Rules/Compile.hs
@@ -69,7 +69,7 @@ compilePackage rs = do
-- or if some of the dynamic artifacts have been removed by the
-- user, "needing" the non dynamic artifacts is not enough as
-- Shake won't execute the associated action. Hence we detect
- -- this case and we explictly build the dynamic artifacts here:
+ -- this case and we explicitly build the dynamic artifacts here:
case changed of
[] -> compileHsObjectAndHi rs dyn_o
_ -> pure ()
diff --git a/includes/rts/FileLock.h b/includes/rts/FileLock.h
index 69df911595..3d8056d7a0 100644
--- a/includes/rts/FileLock.h
+++ b/includes/rts/FileLock.h
@@ -21,7 +21,7 @@
* Instead we keep track of locked files in a data structure in
* the RTS. This file provides the interface to this data structure.
*
- * In the base librarie we then use this interface to "lock" files.
+ * In the base libraries we then use this interface to "lock" files.
* This means it's very much still possible for users outside of the
* rts/base library to open the files in question even if they are
* locked.
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index d18b0ed98d..3c27c6e77e 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -604,7 +604,7 @@ foldMapDefault = coerce (traverse :: (a -> Const m ()) -> t a -> Const m (t ()))
-- Left ("That's odd",9)
--
-- The 'Foldable' instance should be defined in a manner that avoids
--- construction of an unnecesary copy of the container.
+-- construction of an unnecessary copy of the container.
--
-- The @Foldable@ method 'mapM_' and its flipped version 'forM_' can be used
-- to sequence IO actions over all the elements of a @Traversable@ container
diff --git a/libraries/base/GHC/Event/Windows.hsc b/libraries/base/GHC/Event/Windows.hsc
index ea2c51053a..d9a107bbd0 100644
--- a/libraries/base/GHC/Event/Windows.hsc
+++ b/libraries/base/GHC/Event/Windows.hsc
@@ -564,7 +564,7 @@ withOverlappedEx mgr fname h offset startCB completionCB = do
-- relied on for non-file handles we need a way to prevent
-- us from handling a request inline and handle a completion
-- event handled without a queued I/O operation. Which means we
- -- can't solely rely on the number of oustanding requests but most
+ -- can't solely rely on the number of outstanding requests but most
-- also check intermediate status.
reqs <- addRequest
debugIO $ "+1.. " ++ show reqs ++ " requests queued. | " ++ show lpol
diff --git a/libraries/base/GHC/ForeignPtr.hs b/libraries/base/GHC/ForeignPtr.hs
index 718b5a8749..a64d4d19c6 100644
--- a/libraries/base/GHC/ForeignPtr.hs
+++ b/libraries/base/GHC/ForeignPtr.hs
@@ -134,7 +134,7 @@ data ForeignPtrContents
-- reachable (by GC) whenever the 'ForeignPtr' is reachable. When the
-- 'ForeignPtr' becomes unreachable, the runtime\'s normal GC recovers
-- the memory backing it. Here, the finalizer function intended to be used
- -- to @free()@ any ancilliary *unmanaged* memory pointed to by the
+ -- to @free()@ any ancillary *unmanaged* memory pointed to by the
-- 'MutableByteArray#'. See the @zlib@ library for an example of this use.
--
-- 1. Invariant: The 'Addr#' in the parent 'ForeignPtr' is an interior
diff --git a/libraries/base/GHC/IO/Windows/Encoding.hs b/libraries/base/GHC/IO/Windows/Encoding.hs
index c0ee649662..d86487bc5f 100644
--- a/libraries/base/GHC/IO/Windows/Encoding.hs
+++ b/libraries/base/GHC/IO/Windows/Encoding.hs
@@ -9,7 +9,7 @@
Stability : Provisional
Portability : Non-portable (Win32 API)
- Enocode/Decode mutibyte charactor using Win32 API.
+ Enocode/Decode mutibyte character using Win32 API.
-}
module GHC.IO.Windows.Encoding
diff --git a/libraries/base/GHC/IO/Windows/Handle.hsc b/libraries/base/GHC/IO/Windows/Handle.hsc
index ba7f4d1488..9a28b0dda2 100644
--- a/libraries/base/GHC/IO/Windows/Handle.hsc
+++ b/libraries/base/GHC/IO/Windows/Handle.hsc
@@ -884,7 +884,7 @@ openFile' filepath iomode non_blocking tmp_opts =
-- on the Haskell side by using existing mechanisms such as MVar
-- or IOPorts.
then #{const FILE_FLAG_OVERLAPPED}
- -- I beleive most haskell programs do sequential scans, so
+ -- I believe most haskell programs do sequential scans, so
-- optimize for the common case. Though ideally, this would
-- be parameterized by openFile. This will absolutely trash
-- the cache on reverse scans.
diff --git a/libraries/base/Unsafe/Coerce.hs b/libraries/base/Unsafe/Coerce.hs
index 6792592254..7c8e39e92e 100644
--- a/libraries/base/Unsafe/Coerce.hs
+++ b/libraries/base/Unsafe/Coerce.hs
@@ -132,7 +132,7 @@ several ways
x = K a
in ...
Flaoting the case is OK here, even though it broardens the
- scope, becuase we are done with simplification.
+ scope, because we are done with simplification.
(U4) GHC.CoreToStg.Prep.cpeExprIsTrivial anticipates the
upcoming discard of unsafeEqualityProof.
@@ -220,7 +220,7 @@ There are yet more wrinkles
GHCi debugger, and GHCi itself uses unsafeCoerce.
Moreover, in GHC.Tc.Module.tcGhciStmts we use unsafeCoerce#, rather
- than the more kosher unsafeCoerce, becuase (with -O0) the latter
+ than the more kosher unsafeCoerce, because (with -O0) the latter
may not be inlined.
Sigh
diff --git a/libraries/base/tests/perf/Makefile b/libraries/base/tests/perf/Makefile
index 28840dc0b9..8ffa651a33 100644
--- a/libraries/base/tests/perf/Makefile
+++ b/libraries/base/tests/perf/Makefile
@@ -9,7 +9,7 @@ include $(TOP)/mk/test.mk
T17752:
'$(TEST_HC)' $(TEST_HC_OPTS) -O --make T17752 -rtsopts -ddump-simpl -ddump-to-file -dsuppress-uniques -dsuppress-all
- # All occurences of elem should be optimized away.
+ # All occurrences of elem should be optimized away.
# For strings these should result in loops after inlining foldCString.
# For lists it should result in a case expression.
echo $$(cat T17752.dump-simpl | grep "elem" -A4 )
diff --git a/libraries/base/tests/perf/T17752.hs b/libraries/base/tests/perf/T17752.hs
index f7f136e1f4..3c4565ec9c 100644
--- a/libraries/base/tests/perf/T17752.hs
+++ b/libraries/base/tests/perf/T17752.hs
@@ -1,6 +1,6 @@
module T17752 where
--- All occurences of elem should be optimized away.
+-- All occurrences of elem should be optimized away.
-- For strings these should result in loops after inlining foldCString.
-- For lists it should result in a case expression.
diff --git a/libraries/ghc-bignum/src/GHC/Num/Integer.hs b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
index 35afa5d15a..ae0d6af20b 100644
--- a/libraries/ghc-bignum/src/GHC/Num/Integer.hs
+++ b/libraries/ghc-bignum/src/GHC/Num/Integer.hs
@@ -577,7 +577,7 @@ integerTestBit# (IN x) i
| isTrue# (iw >=# n)
= 1#
-- if all the limbs j with j < iw are null, then we have to consider the
- -- carry of the 2's complement convertion. Otherwise we just have to return
+ -- carry of the 2's complement conversion. Otherwise we just have to return
-- the inverse of the bit test
| allZ iw = testBitW# (xi `minusWord#` 1##) ib ==# 0#
| True = testBitW# xi ib ==# 0#
diff --git a/rts/HeapStackCheck.cmm b/rts/HeapStackCheck.cmm
index b8df323c8b..ba89f75522 100644
--- a/rts/HeapStackCheck.cmm
+++ b/rts/HeapStackCheck.cmm
@@ -524,7 +524,7 @@ stg_block_takemvar_finally
jump StgReturn [R1];
}
-// Stack useage covered by RESERVED_STACK_WORDS
+// Stack usage covered by RESERVED_STACK_WORDS
stg_block_takemvar /* mvar passed in R1 */
{
Sp_adj(-2);
diff --git a/rts/RtsAPI.c b/rts/RtsAPI.c
index 3f18a5bc02..d334a05dfb 100644
--- a/rts/RtsAPI.c
+++ b/rts/RtsAPI.c
@@ -720,7 +720,7 @@ PauseToken *rts_pause (void)
Task * task = getMyTask();
if (rts_pausing_task == task)
{
- // This task already pased the RTS.
+ // This task already passed the RTS.
errorBelch("error: rts_pause: This thread has already paused the RTS.");
stg_exit(EXIT_FAILURE);
}
@@ -799,7 +799,7 @@ static void assert_isPausedOnMyTask(const char *functionName)
if (task != rts_pausing_task)
{
// We don't have ownership of rts_pausing_task, so it may have changed
- // just after the above read. Still, we are garanteed that
+ // just after the above read. Still, we are guaranteed that
// rts_pausing_task won't be set to the current task (because the
// current task is here now!), so the error messages are still correct.
errorBelch (
diff --git a/rts/RtsFlags.c b/rts/RtsFlags.c
index ddd561b29c..380ccc3afc 100644
--- a/rts/RtsFlags.c
+++ b/rts/RtsFlags.c
@@ -502,7 +502,7 @@ usage_text[] = {
#if defined(mingw32_HOST_OS)
" --io-manager-threads=<num>",
" The number of worker threads to use in the native I/O manager to",
-" handle completion events. (defualt: num cores)",
+" handle completion events. (default: num cores)",
#endif
" -e<n> Maximum number of outstanding local sparks (default: 4096)",
#endif
diff --git a/rts/Stats.c b/rts/Stats.c
index 53251bb7d6..2770696b66 100644
--- a/rts/Stats.c
+++ b/rts/Stats.c
@@ -1595,7 +1595,7 @@ Parallel garbage collector counters:
* scav_find_work:
Counts iterations of scavenge loop
* max_n_todo_overflow:
- Tracks the maximum length of todo_overflow lists in the gc_thread structre.
+ Tracks the maximum length of todo_overflow lists in the gc_thread structure.
See comment in grab_local_todo_block.
*/
diff --git a/rts/sm/GC.c b/rts/sm/GC.c
index 0f9a9eaa84..6d222da02a 100644
--- a/rts/sm/GC.c
+++ b/rts/sm/GC.c
@@ -1412,7 +1412,7 @@ waitForGcThreads (Capability *cap, bool idle_cap[])
}
}
- ASSERT(n_threads < n_capabilities); // must be less becasue we don't count ourself
+ ASSERT(n_threads < n_capabilities); // must be less because we don't count ourself
if(n_threads == 0) { return; }
ACQUIRE_LOCK(&gc_entry_mutex);
diff --git a/rts/win32/AsyncWinIO.c b/rts/win32/AsyncWinIO.c
index 0c0b45e60f..7fb71e92e7 100644
--- a/rts/win32/AsyncWinIO.c
+++ b/rts/win32/AsyncWinIO.c
@@ -149,7 +149,7 @@
* call ioManagerStart()
* Creat a thread to execute "runner"
- We never truely shut down the IO Manager. While this means we
+ We never truly shut down the IO Manager. While this means we
might block forever on the IOPort if the IO Manager is no longer
needed we consider this cheap compared to the complexity of
properly handling pausing and resuming of the manager.
@@ -284,7 +284,7 @@ void shutdownAsyncWinIO(bool wait_threads)
ioManagerDie ();
}
-/* Register the I/O completetion port handle PORT that the I/O manager will be
+/* Register the I/O completion port handle PORT that the I/O manager will be
monitoring. All handles are expected to be associated with this handle. */
void registerIOCPHandle (HANDLE port)
{
@@ -365,7 +365,7 @@ void registerAlertableWait (bool has_timeout, DWORD mssec)
ReleaseSRWLockExclusive (&wio_runner_lock);
/* Since we call registerAlertableWait only after
- processing I/O requests it's always desireable to wake
+ processing I/O requests it's always desirable to wake
up the runner here. */
WakeConditionVariable (&wakeEvent);
diff --git a/testsuite/driver/perf_notes.py b/testsuite/driver/perf_notes.py
index eb31f463da..a320f22336 100644
--- a/testsuite/driver/perf_notes.py
+++ b/testsuite/driver/perf_notes.py
@@ -487,7 +487,7 @@ def get_commit_metric_value_str_or_none(gitNoteRef,
return str(result.value)
# gets the average commit metric from git notes.
-# gitNoteRef: git notes ref sapce e.g. "perf" or "ci/perf"
+# gitNoteRef: git notes ref space e.g. "perf" or "ci/perf"
# ref: git commit
# test_env: test environment
# name: test name
diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py
index 5826a976e1..2b3dd48b68 100644
--- a/testsuite/driver/testglobals.py
+++ b/testsuite/driver/testglobals.py
@@ -169,7 +169,7 @@ class TestConfig:
# run.
self.broken_tests = set() # type: Set[TestName]
- # Baseline commit for performane metric comparisons.
+ # Baseline commit for performance metric comparisons.
self.baseline_commit = None # type: Optional[GitRef]
# Additional package dbs to inspect for test dependencies.
diff --git a/testsuite/tests/codeGen/should_run/cgrun069_cmm.cmm b/testsuite/tests/codeGen/should_run/cgrun069_cmm.cmm
index 006595e319..989251d646 100644
--- a/testsuite/tests/codeGen/should_run/cgrun069_cmm.cmm
+++ b/testsuite/tests/codeGen/should_run/cgrun069_cmm.cmm
@@ -139,7 +139,7 @@ loop_end: \
foreign "C" free(dst); \
return (0);
-// This is not exactly beutiful but we need the separate functions to
+// This is not exactly beautiful but we need the separate functions to
// avoid collisions between labels.
//
// The specific tests are selected with knowledge of the implementation
diff --git a/testsuite/tests/dynlibs/all.T b/testsuite/tests/dynlibs/all.T
index 092c983389..79d4ee9c5a 100644
--- a/testsuite/tests/dynlibs/all.T
+++ b/testsuite/tests/dynlibs/all.T
@@ -20,5 +20,5 @@ test('T18072', [req_shared_libs, unless(opsys('linux'), skip)], makefile_test, [
# test that -shared and -flink-rts respects alternative RTS flavours
test('T18072debug', [extra_files(['T18072.hs']), req_shared_libs, unless(opsys('linux'), skip)], makefile_test, [])
-# check that -staticlib and -fno-link-rts results in an archive without the RTR libary
+# check that -staticlib and -fno-link-rts results in an archive without the RTR library
test('T18072static', [extra_files(['T18072.hs']), unless(opsys('linux'), skip)], makefile_test, [])
diff --git a/testsuite/tests/gadt/SynDataRec.hs b/testsuite/tests/gadt/SynDataRec.hs
index 021ed0ba17..fe290a8cae 100644
--- a/testsuite/tests/gadt/SynDataRec.hs
+++ b/testsuite/tests/gadt/SynDataRec.hs
@@ -2,7 +2,7 @@
module SynDataRec where
--- This mutual recursion betwen a data type and
+-- This mutual recursion between a data type and
-- a type synonym is a little delicate. See
-- Note [GADT return types] in GHC.Tc.TyCl
diff --git a/testsuite/tests/hiefile/should_compile/Scopes.hs b/testsuite/tests/hiefile/should_compile/Scopes.hs
index 21766c6446..a6714a9a68 100644
--- a/testsuite/tests/hiefile/should_compile/Scopes.hs
+++ b/testsuite/tests/hiefile/should_compile/Scopes.hs
@@ -6,7 +6,7 @@
module Scopes where
--- Verify that evidence bound by patern
+-- Verify that evidence bound by pattern
-- synonyms has correct scope
pattern LL :: Num a => a -> a
pattern LL x <- (subtract 1 -> x)
@@ -19,7 +19,7 @@ data T = C { x :: Int, y :: Char }
-- have correct scope
foo = C { x = 1 , y = 'a' }
--- Verify that implicit paramters have correct scope
+-- Verify that implicit parameters have correct scope
bar :: (?x :: Int) => Int
bar = ?x + 1
diff --git a/testsuite/tests/indexed-types/should_compile/T18809.hs b/testsuite/tests/indexed-types/should_compile/T18809.hs
index 1e56d980f6..0135c4e370 100644
--- a/testsuite/tests/indexed-types/should_compile/T18809.hs
+++ b/testsuite/tests/indexed-types/should_compile/T18809.hs
@@ -16,7 +16,7 @@ data F1 s where
bar1 :: F1 s -> Int -> F1 s
bar1 z y = z { foo1 = y }
--- Orinary data family
+-- Ordinary data family
data family F3 a
data instance F3 (s,t) where
MkF2b :: { foo3 :: Int } -> F3 (s,t)
diff --git a/testsuite/tests/linear/should_compile/CSETest.hs b/testsuite/tests/linear/should_compile/CSETest.hs
index 3321dbd43d..71f807dc26 100644
--- a/testsuite/tests/linear/should_compile/CSETest.hs
+++ b/testsuite/tests/linear/should_compile/CSETest.hs
@@ -2,7 +2,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE UnicodeSyntax #-}
{- This test makes sure that if two expressions with conflicting types are
- CSEd then appropiate things happen. -}
+ CSEd then appropriate things happen. -}
module CSETest where
minimal :: a ⊸ a
diff --git a/testsuite/tests/pmcheck/should_compile/T17340.hs b/testsuite/tests/pmcheck/should_compile/T17340.hs
index fa2ef60812..b3d69b4da2 100644
--- a/testsuite/tests/pmcheck/should_compile/T17340.hs
+++ b/testsuite/tests/pmcheck/should_compile/T17340.hs
@@ -51,4 +51,4 @@ w _ _ = ()
z :: T2 a -> Bool -> ()
z _ True = ()
z t2 !x | T2 _ <- t2, x = () -- redundant
- | !_ <- t2, x = () -- inaccessable
+ | !_ <- t2, x = () -- inaccessible
diff --git a/testsuite/tests/pmcheck/should_compile/T18478.hs b/testsuite/tests/pmcheck/should_compile/T18478.hs
index 372ac2d171..6739388d99 100644
--- a/testsuite/tests/pmcheck/should_compile/T18478.hs
+++ b/testsuite/tests/pmcheck/should_compile/T18478.hs
@@ -530,7 +530,7 @@ forbiddenOpEvi = Sub $
OpAbsent -> Dict
OpPresent -> error "impossible"
--- | Reify 'HasNoOp' contraint from 'ForbidOp'.
+-- | Reify 'HasNoOp' constraint from 'ForbidOp'.
--
-- Left for backward compatibility.
forbiddenOp
@@ -566,7 +566,7 @@ forbiddenNestedBigMaps
-> a
forbiddenNestedBigMaps = withDict $ forbiddenNestedBigMapsEvi @t
--- | Reify 'HasNoContract' contraint from 'ForbidContract'.
+-- | Reify 'HasNoContract' constraint from 'ForbidContract'.
forbiddenContractTypeEvi
:: forall t. (SingI t, ForbidContract t) :- HasNoContract t
forbiddenContractTypeEvi = Sub $
@@ -574,7 +574,7 @@ forbiddenContractTypeEvi = Sub $
ContractAbsent -> Dict
ContractPresent -> error "impossible"
--- | Reify 'HasNoContract' contraint from 'ForbidContract'.
+-- | Reify 'HasNoContract' constraint from 'ForbidContract'.
forbiddenContractType
:: forall t a.
(SingI t, ForbidContract t)
diff --git a/testsuite/tests/stranal/should_run/T13380d.hs b/testsuite/tests/stranal/should_run/T13380d.hs
index 440c4ced1e..3430c958c0 100644
--- a/testsuite/tests/stranal/should_run/T13380d.hs
+++ b/testsuite/tests/stranal/should_run/T13380d.hs
@@ -5,7 +5,7 @@ import Control.Exception
import GHC.Exts
import GHC.IO
--- | An "unboxed" IO action that throws a precise excpetion that isn't inlined.
+-- | An "unboxed" IO action that throws a precise exception that isn't inlined.
throws :: State# RealWorld -> State# RealWorld
throws s = case raiseIO# (toException (userError "What")) s of (# s', _ #) -> s'
{-# NOINLINE throws #-}
diff --git a/testsuite/tests/stranal/should_run/T13380e.hs b/testsuite/tests/stranal/should_run/T13380e.hs
index d807db091b..b69dfd51e9 100644
--- a/testsuite/tests/stranal/should_run/T13380e.hs
+++ b/testsuite/tests/stranal/should_run/T13380e.hs
@@ -3,7 +3,7 @@ import Control.Exception
-- This is just like T13380d, but doesn't look through the IO abstraction.
-- With Nested CPR, it will result in very similar code, however!
--- | An IO action that throws a precise excpetion that isn't inlined.
+-- | An IO action that throws a precise exception that isn't inlined.
throws :: IO ()
throws = throwIO (userError "What")
{-# NOINLINE throws #-}
diff --git a/testsuite/tests/stranal/sigs/T18086.hs b/testsuite/tests/stranal/sigs/T18086.hs
index 639409adce..9a6f67c6d1 100644
--- a/testsuite/tests/stranal/sigs/T18086.hs
+++ b/testsuite/tests/stranal/sigs/T18086.hs
@@ -13,7 +13,7 @@ m = do
putStrLn "foo"
error "bar"
--- Dito, just in a more complex scenario (the original reproducer of #18086)
+-- Ditto, just in a more complex scenario (the original reproducer of #18086)
panic :: String -> a
panic x = unsafeDupablePerformIO $ do
stack <- ccsToStrings =<< getCurrentCCS x
diff --git a/testsuite/tests/typecheck/should_fail/T17173.hs b/testsuite/tests/typecheck/should_fail/T17173.hs
index d26c5dd619..e1c3dbfc0c 100644
--- a/testsuite/tests/typecheck/should_fail/T17173.hs
+++ b/testsuite/tests/typecheck/should_fail/T17173.hs
@@ -2,5 +2,5 @@
module T17173 where
--- This now fails with eager instantation
+-- This now fails with eager instantiation
foo = (let myId :: forall a. a -> a; myId x = x in myId) @Bool True
diff --git a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs
index 01afc9cb42..fc3e7b583e 100644
--- a/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs
+++ b/testsuite/tests/typecheck/should_fail/TcCoercibleFail.hs
@@ -22,7 +22,7 @@ foo5 = coerce :: Void -> ()
------------------------------------
--- This next one generates an exponentally big type as it
+-- This next one generates an exponentially big type as it
-- tries to unwrap. See comment:15 in #11518
-- Adding assertions that force the types can make us
-- run out of space.