diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs
index 3226a8773d85f300c5fd6ab32411a2b4f9061788..23e4f0ea742ae4d4de0f7df5431bb6e76d839350 100644
--- a/compiler/deSugar/Check.hs
+++ b/compiler/deSugar/Check.hs
@@ -578,7 +578,7 @@ Which means that in source Haskell:
 -- | Generate all inhabitation candidates for a given type. The result is
 -- either (Left ty), if the type cannot be reduced to a closed algebraic type
 -- (or if it's one trivially inhabited, like Int), or (Right candidates), if it
--- can. In this case, the candidates are the singnature of the tycon, each one
+-- can. In this case, the candidates are the signature of the tycon, each one
 -- accompanied by the term- and type- constraints it gives rise to.
 -- See also Note [Checking EmptyCase Expressions]
 inhabitationCandidates :: FamInstEnvs -> Type
diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp
index afe58498db3d51466ada8289a51fc9ca5ef5c073..a314ebf46a2e23a6bd47556718f4ce8bfbed1809 100644
--- a/compiler/prelude/primops.txt.pp
+++ b/compiler/prelude/primops.txt.pp
@@ -2113,7 +2113,7 @@ primop  AtomicallyOp "atomically#" GenPrimOp
 --   retry# s1
 -- where 'e' would be unreachable anyway.  See Trac #8091.
 --
--- Note that it *does not* return botRes as the "exception" that is throw may be
+-- Note that it *does not* return botRes as the "exception" that is thrown may be
 -- "caught" by catchRetry#. This mistake caused #14171.
 primop  RetryOp "retry#" GenPrimOp
    State# RealWorld -> (# State# RealWorld, a #)
@@ -2869,7 +2869,7 @@ pseudoop   "unsafeCoerce#"
         {\tt unsafeCoerce\#} to cast a T to an algebraic data type D, unless T is also
         an algebraic data type.  For example, do not cast {\tt Int->Int} to {\tt Bool}, even if
         you later cast that {\tt Bool} back to {\tt Int->Int} before applying it.  The reasons
-        have to do with GHC's internal representation details (for the congnoscenti, data values
+        have to do with GHC's internal representation details (for the cognoscenti, data values
         can be entered but function closures cannot).  If you want a safe type to cast things
         to, use {\tt Any}, which is not an algebraic data type.
 
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index df47da3e327f257bb950e942a5002545ed64dc1c..fbfd017f235c0979427135afee123393607e55dc 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -2052,17 +2052,17 @@ Where do we find the TyCon?  For good reasons we only have constraint
 tuples up to 62 (see Note [How tuples work] in TysWiredIn).  So how
 can we make a 70-tuple?  This was the root cause of Trac #14217.
 
-It's incredibly tiresome, becuase we only need this type to fill
-in the hole, to commuincate to the error reporting machinery.  Nothing
+It's incredibly tiresome, because we only need this type to fill
+in the hole, to communicate to the error reporting machinery.  Nothing
 more.  So I use a HACK:
 
 * I make an /ordinary/ tuple of the constraints, in
   TcBinds.chooseInferredQuantifiers. This is ill-kinded because
-  ordinary tuples can't contain contraints, but it works fine. And for
+  ordinary tuples can't contain constraints, but it works fine. And for
   ordinary tuples we don't have the same limit as for constraint
   tuples (which need selectors and an assocated class).
 
-* Because it is ill-kided, it trips an assert in writeMetaTyVar,
+* Because it is ill-kinded, it trips an assert in writeMetaTyVar,
   so now I disable the assertion if we are writing a type of
   kind Constraint.  (That seldom/never normally happens so we aren't
   losing much.)
@@ -2208,7 +2208,7 @@ Here
 
  * Finally, in 'blah' we must have the envt "b" :-> a_sk.  The pair
    ("b" :-> a_sk) is returned by tcHsPatSigType, constructed by
-   mk_tv_pair in that funcion.
+   mk_tv_pair in that function.
 
 Another example (Trac #13881):
    fl :: forall (l :: [a]). Sing l -> Sing l
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index f95194f5ea5448ebcb5c8e4e97f487c5e3ae74de..3d506f6797c3be264774baf14be6d0dd05041982 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -2297,7 +2297,7 @@ this:
 Faced with [W] t1 ~~ t2, it's always OK to reduce it to [W] t1 ~# t2,
 without worrying about Note [Instance and Given overlap].  Why?  Because
 if we had [G] s1 ~~ s2, then we'd get the superclass [G] s1 ~# s2, and
-so the reduction of the [W] contraint does not risk losing any solutions.
+so the reduction of the [W] constraint does not risk losing any solutions.
 
 On the other hand, it can be fatal to /fail/ to reduce such
 equalities, on the grounds of Note [Instance and Given overlap],
diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs
index 0e88e237e65a032286fb2a1a9f4ba8820f29ebbf..fd288ebd741d19591be99e0c61217a7ec7133fc5 100644
--- a/compiler/typecheck/TcRnMonad.hs
+++ b/compiler/typecheck/TcRnMonad.hs
@@ -1576,7 +1576,7 @@ looks :-).
 
 However suppose we throw an exception inside an invocation of
 captureConstraints, and discard all the constraints. Some of those
-contraints might be "variable out of scope" Hole constraints, and that
+constraints might be "variable out of scope" Hole constraints, and that
 might have been the actual original cause of the exception!  For
 example (Trac #12529):
    f = p @ Int
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index 21765a67b9e2a0c92ba088ecf7dbe3f57bd14bd8..ba0777bc6203f79c2e86a5d78eb5de2cadd05b45 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -1201,7 +1201,7 @@ Here's the invariant:
    Specifically,
        a) The Id's acutal type is closed (has no free tyvars)
        b) Either the Id has a (closed) user-supplied type signature
-          or all its free varaibles are Global/ClosedLet
+          or all its free variables are Global/ClosedLet
              or NonClosedLet with ClosedTypeId=True.
           In particular, none are NotLetBound.
 
diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs
index bcd26bbc46bf48aa87da863964781beb917f60aa..cec273525816e56af043c79cb307e0ca10b4efd7 100644
--- a/compiler/typecheck/TcSMonad.hs
+++ b/compiler/typecheck/TcSMonad.hs
@@ -2132,7 +2132,7 @@ Consider
    f,g :: (?x::Int, C a) => a -> a
    f v = let ?x = 4 in g v
 
-The call to 'g' gives rise to a Wanted contraint (?x::Int, C a).
+The call to 'g' gives rise to a Wanted constraint (?x::Int, C a).
 We must /not/ solve this from the Given (?x::Int, C a), because of
 the intervening binding for (?x::Int).  Trac #14218.
 
@@ -2160,7 +2160,7 @@ Suppose f :: HasCallStack => blah.  Then
    Bind:  s1 = pushCallStack <site-info> s2
    [W] s2 :: IP "callStack" CallStack   -- CtOrigin = IPOccOrigin
 
-* Then, and only then, we can solve the contraint from an enclosing
+* Then, and only then, we can solve the constraint from an enclosing
   Given.
 
 So we must be careful /not/ to solve 's1' from the Givens.  Again,
diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs
index 457d012504459694ac25168461ed5a6fb9be1eb5..b401e1b5ced8f175894ac9942e933136fb56d6b4 100644
--- a/compiler/types/Unify.hs
+++ b/compiler/types/Unify.hs
@@ -804,7 +804,7 @@ Note that
   better way.
 
 * One better way is to ensure that type patterns (the template
-  in the matchingn process) have no casts.  See Trac #14119.
+  in the matching process) have no casts.  See Trac #14119.
 
 -}
 
diff --git a/testsuite/tests/deriving/should_compile/drv-functor1.hs b/testsuite/tests/deriving/should_compile/drv-functor1.hs
index 8249858cae49bd16ef261ccacc7f747e97d9a732..040d531341ef29c0a73665fcfcdd77f0a69e01d7 100644
--- a/testsuite/tests/deriving/should_compile/drv-functor1.hs
+++ b/testsuite/tests/deriving/should_compile/drv-functor1.hs
@@ -41,7 +41,7 @@ data Compose f g a = Compose (f (g a))
 -- i.e.:
 --  instance (Functor (f Bool), Functor (f Int)) => Functor (ComplexConstraint f)
 -- This requires FlexibleContexts and UndecidableInstances
-data ComplexConstraint f a = ComplexContraint (f Int (f Bool a,a))
+data ComplexConstraint f a = ComplexConstraint (f Int (f Bool a,a))
 --  deriving (Functor)
 
 data Universal a
diff --git a/testsuite/tests/programs/andy_cherry/andy_cherry.stdout b/testsuite/tests/programs/andy_cherry/andy_cherry.stdout
index da1bf8c8bd4d5ba5be2580f66535a8e6084aa859..743174dce85aba7d850f2bd6d153a2a81931f366 100644
--- a/testsuite/tests/programs/andy_cherry/andy_cherry.stdout
+++ b/testsuite/tests/programs/andy_cherry/andy_cherry.stdout
@@ -67,7 +67,7 @@ $$\showboard$$
 6 & N*e4?&\\
 \end{tabular}}|
 \end{center}
-Taking this knight looses a pawn
+Taking this knight loses a pawn
 \begin{center}|
 {\bf\begin{tabular}{rp{50pt}p{50pt}}
 6 & \ldots & d*e4\\
@@ -4764,7 +4764,7 @@ Edinburgh Congress
 25 & h3&\\
 \end{tabular}}|
 \end{center}
-At this point the score sheet goes wrong. Black eventually looses on
+At this point the score sheet goes wrong. Black eventually loses on
 time!
 
 \board
diff --git a/testsuite/tests/programs/andy_cherry/mygames.pgn b/testsuite/tests/programs/andy_cherry/mygames.pgn
index 697b4d66f0181444dfabc04c2d28e5e958f391d5..9a338cf05ebfea1d11eaef85070bcf0af3980b4e 100644
--- a/testsuite/tests/programs/andy_cherry/mygames.pgn
+++ b/testsuite/tests/programs/andy_cherry/mygames.pgn
@@ -13,7 +13,7 @@
 1. Nf3 d5 2. d4 Nc6 3. Nc3 Nf6 (3... Bf5 {is more natural.}) 4. e4? (
 4. Bf4 {is better.}) 4... e6? (4... dxe4 5. d5 exf3 6. dxc6 Qxd1+ 7. 
 Nxd1 {and black is a clear pawn up.}) 5. e5 Ne4 {} 6. Nxe4? { Taking
-this knight looses a pawn} 6... dxe4 7. Nd2 Qxd4 8. Nc4 Qxd1+ 9. Kxd1 
+this knight loses a pawn} 6... dxe4 7. Nd2 Qxd4 8. Nc4 Qxd1+ 9. Kxd1 
 Bd7 (9... Bc5 10. f3 exf3 11. gxf3 O-O 12. Bd3 {White can get presure
 down the `g' file, but first needs to solve the problem of the Bishop on
 c5 guarding g8.}) 10. Bd2 (10. Be3 {is better.}) 10... Bb4 11. c3 Bc5 12. 
@@ -890,7 +890,7 @@ Nf3 Rb2 36. h4 d2 37. Nxd2 Rxd2 38. Kg4 Rd3 39. Rxd3 Bxd3 40. Kf3 Bc4
 14. Re1 h6 15. Bxe7 Qxe7 16. exf5 Qf6 17. Be4 Bb7 18. Bxb7 Nxb7 19. 
 Qb3+ Kh8 20. Qd5 Rab8 21. Rac1 Bb6 22. g4 Nd8 23. Ne4 Qf7 24. Qxf7 Rxf7 
 25. h3 {At this point the score sheet goes wrong. Black eventually
-looses on time!} 1-0
+loses on time!} 1-0
 
 [Site "Edinburgh Congress"]
 [Date "1994.04.??"]