summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/codeGen/StgCmmMonad.hs4
-rw-r--r--compiler/deSugar/Check.hs2
-rw-r--r--compiler/deSugar/Match.hs2
-rw-r--r--compiler/main/HscMain.hs2
-rw-r--r--compiler/simplCore/CallArity.hs4
-rw-r--r--compiler/simplCore/Simplify.hs2
-rw-r--r--compiler/simplStg/StgCse.hs2
-rw-r--r--compiler/typecheck/TcExpr.hs2
-rw-r--r--compiler/typecheck/TcInteract.hs2
-rw-r--r--compiler/typecheck/TcRnTypes.hs12
-rw-r--r--compiler/typecheck/TcSigs.hs2
-rw-r--r--compiler/typecheck/TcSimplify.hs4
-rw-r--r--compiler/typecheck/TcValidity.hs2
-rw-r--r--ghc/GHCi/UI/Tags.hs4
-rw-r--r--testsuite/README.md2
-rw-r--r--testsuite/tests/gadt/T9380.hs2
-rw-r--r--testsuite/tests/partial-sigs/should_fail/PatBind3.hs2
-rw-r--r--testsuite/tests/pmcheck/complete_sigs/completesig10.hs2
-rw-r--r--testsuite/tests/simplStg/should_run/T13536.hs2
-rw-r--r--testsuite/tests/simplStg/should_run/T13536.stderr2
20 files changed, 29 insertions, 29 deletions
diff --git a/compiler/codeGen/StgCmmMonad.hs b/compiler/codeGen/StgCmmMonad.hs
index bb093a5e51..cf78269cc5 100644
--- a/compiler/codeGen/StgCmmMonad.hs
+++ b/compiler/codeGen/StgCmmMonad.hs
@@ -288,8 +288,8 @@ data ReturnKind
--
-- Since this case is so common I decided to make it more explicit and
-- robust by programming the sharing directly, rather than relying on
--- the common-block elimiantor to catch it. This makes
--- common-block-elimianteion an optional optimisation, and furthermore
+-- the common-block eliminator to catch it. This makes
+-- common-block-elimination an optional optimisation, and furthermore
-- generates less code in the first place that we have to subsequently
-- clean up.
--
diff --git a/compiler/deSugar/Check.hs b/compiler/deSugar/Check.hs
index 792932df5a..c08353a15b 100644
--- a/compiler/deSugar/Check.hs
+++ b/compiler/deSugar/Check.hs
@@ -91,7 +91,7 @@ liftD m = ListT $ \sk fk -> m >>= \a -> sk a fk
-- Pick the first match complete covered match or otherwise the "best" match.
-- The best match is the one with the least uncovered clauses, ties broken
--- by the number of inaccessible clauses followed by number of redudant
+-- by the number of inaccessible clauses followed by number of redundant
-- clauses
getResult :: PmM PmResult -> DsM PmResult
getResult ls = do
diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs
index 33dd7990c7..abe4dc77b2 100644
--- a/compiler/deSugar/Match.hs
+++ b/compiler/deSugar/Match.hs
@@ -159,7 +159,7 @@ corresponds roughly to @matchVarCon@.
Note [Match Ids]
~~~~~~~~~~~~~~~~
-Most of the matching fuctions take an Id or [Id] as argument. This Id
+Most of the matching functions take an Id or [Id] as argument. This Id
is the scrutinee(s) of the match. The desugared expression may
sometimes use that Id in a local binding or as a case binder. So it
should not have an External name; Lint rejects non-top-level binders
diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index fd8c2c0ca9..d6630c3282 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -344,7 +344,7 @@ hscParse' mod_summary
-- that the parser gave us,
-- - eliminate files beginning with '<'. gcc likes to use
-- pseudo-filenames like "<built-in>" and "<command-line>"
- -- - normalise them (elimiante differences between ./f and f)
+ -- - normalise them (eliminate differences between ./f and f)
-- - filter out the preprocessed source file
-- - filter out anything beginning with tmpdir
-- - remove duplicates
diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs
index 2e1de85ad7..e23314b569 100644
--- a/compiler/simplCore/CallArity.hs
+++ b/compiler/simplCore/CallArity.hs
@@ -409,7 +409,7 @@ Call Arity considers everything that is not cheap (`exprIsCheap`) as a thunk.
Note [Call Arity and Join Points]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The Call Arity analysis does not care about joint points, and treats them just
+The Call Arity analysis does not care about join points, and treats them just
like normal functions. This is ok.
The analysis *could* make use of the fact that join points are always evaluated
@@ -420,7 +420,7 @@ This *might* be more efficient (for example, join points would not have to be
considered interesting variables), but it would also add redundant code. So for
now we do not do that.
-The simplifier never eta-expands join points (it insteads pushes extra arguments from
+The simplifier never eta-expands join points (it instead pushes extra arguments from
an eta-expanded context into the join point’s RHS), so the call arity
annotation on join points is not actually used. As it would be equally valid
(though less efficient) to eta-expand join points, this is the simplifier's
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index fe8c578106..78ef3927f2 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -2408,7 +2408,7 @@ then we'd like to transform
Nota Bene: we used to have a built-in rule for 'seq' that dropped
casts, so that
case (x |> co) of { _ -> blah }
-dropped the cast; in order to imporove the chances of trySeqRules
+dropped the cast; in order to improve the chances of trySeqRules
firing. But that works in the /opposite/ direction to Note [Improving
seq] so there's a danger of flip/flopping. Better to make trySeqRules
insensitive to the cast, which is now is.
diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs
index c0063814d7..1ee6a9a150 100644
--- a/compiler/simplStg/StgCse.hs
+++ b/compiler/simplStg/StgCse.hs
@@ -392,7 +392,7 @@ mkStgLet stgLet (Just binds) body = stgLet binds body
{-
Note [Trivial case scrutinee]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We wnat to be able to handle nested reconstruction of constructors as in
+We want to be able to handle nested reconstruction of constructors as in
nested :: Either Int (Either Int a) -> Either Bool (Either Bool a)
nested (Right (Right v)) = Right (Right v)
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index cbe94eaecb..48252dffc6 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -1538,7 +1538,7 @@ tcExprSig expr sig@(PartialSig { psig_name = name, sig_loc = loc })
my_sigma = mkForAllTys binders (mkPhiTy my_theta tau)
; wrap <- if inferred_sigma `eqType` my_sigma -- NB: eqType ignores vis.
then return idHsWrapper -- Fast path; also avoids complaint when we infer
- -- an ambiguouse type and have AllowAmbiguousType
+ -- an ambiguous type and have AllowAmbiguousType
-- e..g infer x :: forall a. F a -> Int
else tcSubType_NC ExprSigCtxt inferred_sigma my_sigma
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index 13485d5119..5792dfbb67 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -1077,7 +1077,7 @@ f2 :: (?x :: Int, ?x :: Char) => Int
f2 = ?x
Both of these are actually wrong: when we try to use either one,
-we'll get two incompatible wnated constraints (?x :: Int, ?x :: Char),
+we'll get two incompatible wanted constraints (?x :: Int, ?x :: Char),
which would lead to an error.
I can think of two ways to fix this:
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index c004052483..e4a034b5f9 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -1816,15 +1816,15 @@ dropDerivedInsols insols = filterBag keep insols
| otherwise = True
isDroppableDerivedLoc :: CtLoc -> Bool
--- Note [Dropping derived constraints]
+-- See Note [Dropping derived constraints]
isDroppableDerivedLoc loc
= case ctLocOrigin loc of
HoleOrigin {} -> False
KindEqOrigin {} -> False
GivenOrigin {} -> False
- -- See Note [Dropping derived constraints
- -- For fundeps, drop wanted/warnted interactions
+ -- See Note [Dropping derived constraints]
+ -- For fundeps, drop wanted/wanted interactions
FunDepOrigin2 {} -> False
FunDepOrigin1 _ loc1 _ loc2
| isGivenLoc loc1 || isGivenLoc loc2 -> False
@@ -1861,8 +1861,8 @@ see dropDerivedWC. For example
But (tiresomely) we do keep *some* Derived insolubles:
- * Type holes are derived constraints because they have no evidence
- and we want to keep them so we get the error report
+ * Type holes are derived constraints, because they have no evidence
+ and we want to keep them, so we get the error report
* Insoluble derived equalities (e.g. [D] Int ~ Bool) may arise from
functional dependency interactions:
@@ -2182,7 +2182,7 @@ trulyInsoluble :: Ct -> Bool
-- a) type holes, arising from PartialTypeSignatures,
-- b) "true" expression holes arising from TypedHoles
--
--- A "expression hole" or "type hole" constraint isn't really an error
+-- An "expression hole" or "type hole" constraint isn't really an error
-- at all; it's a report saying "_ :: Int" here. But an out-of-scope
-- variable masquerading as expression holes IS treated as truly
-- insoluble, so that it trumps other errors during error reporting.
diff --git a/compiler/typecheck/TcSigs.hs b/compiler/typecheck/TcSigs.hs
index 989fe94e8c..0a8fb5e35c 100644
--- a/compiler/typecheck/TcSigs.hs
+++ b/compiler/typecheck/TcSigs.hs
@@ -754,7 +754,7 @@ tcImpPrags prags
-- Ignore SPECIALISE pragmas for imported things
-- when we aren't specialising, or when we aren't generating
-- code. The latter happens when Haddocking the base library;
- -- we don't wnat complaints about lack of INLINABLE pragmas
+ -- we don't want complaints about lack of INLINABLE pragmas
not_specialising dflags
| not (gopt Opt_Specialise dflags) = True
| otherwise = case hscTarget dflags of
diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index 58830ec645..4d5772d059 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -787,7 +787,7 @@ If the monomorphism restriction does not apply, then we quantify as follows:
Motivation for re-simplification (Trac #7857): imagine we have a
constraint (C (a->b)), where 'a :: TYPE l1' and 'b :: TYPE l2' are
not free in the envt, and instance forall (a::*) (b::*). (C a) => C
- (a -> b) The instance doesnt' match while l1,l2 are polymorphic, but
+ (a -> b) The instance doesn't match while l1,l2 are polymorphic, but
it will match when we default them to LiftedRep.
This is all very tiresome.
@@ -901,7 +901,7 @@ defaultTyVarsAndSimplify :: TcLevel
-> [PredType] -- Assumed zonked
-> TcM [PredType] -- Guaranteed Zonked
-- Default any tyvar free in the constraints,
--- and re-simplify in case the defaulting allows futher simplification
+-- and re-simplify in case the defaulting allows further simplification
defaultTyVarsAndSimplify rhs_tclvl mono_tvs candidates
| null candidates -- Common shortcut
= return []
diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs
index c28c21da97..0a7a0adf7f 100644
--- a/compiler/typecheck/TcValidity.hs
+++ b/compiler/typecheck/TcValidity.hs
@@ -1997,7 +1997,7 @@ sizeTypes = sum . map sizeType
--
-- We are considering whether class constraints terminate.
-- Equality constraints and constraints for the implicit
--- parameter class always termiante so it is safe to say "size 0".
+-- parameter class always terminate so it is safe to say "size 0".
-- (Implicit parameter constraints always terminate because
-- there are no instances for them---they are only solved by
-- "local instances" in expressions).
diff --git a/ghc/GHCi/UI/Tags.hs b/ghc/GHCi/UI/Tags.hs
index 8a06eb3583..c23db57f81 100644
--- a/ghc/GHCi/UI/Tags.hs
+++ b/ghc/GHCi/UI/Tags.hs
@@ -143,12 +143,12 @@ writeTagsSafely file str = do
else writeFile file str
collateAndWriteTags :: TagsKind -> FilePath -> [TagInfo] -> IO (Either IOError ())
--- ctags style with the Ex exresion being just the line number, Vim et al
+-- ctags style with the Ex expression being just the line number, Vim et al
collateAndWriteTags CTagsWithLineNumbers file tagInfos = do
let tags = unlines $ sort $ map showCTag tagInfos
tryIO (writeTagsSafely file tags)
--- ctags style with the Ex exresion being a regex searching the line, Vim et al
+-- ctags style with the Ex expression being a regex searching the line, Vim et al
collateAndWriteTags CTagsWithRegExes file tagInfos = do -- ctags style, Vim et al
tagInfoGroups <- makeTagGroupsWithSrcInfo tagInfos
let tags = unlines $ sort $ map showCTag $concat tagInfoGroups
diff --git a/testsuite/README.md b/testsuite/README.md
index 5ab6dafb34..278a668e86 100644
--- a/testsuite/README.md
+++ b/testsuite/README.md
@@ -17,7 +17,7 @@ Commands to run testsuite:
* Test a specifc stage of GHC: `make stage=1`
* Skip performance tests: `make SKIP_PERF_TESTS=YES`
* Set verbosity: `make VERBOSE=n`
- where n=0: No per-test ouput, n=1: Only failures,
+ where n=0: No per-test output, n=1: Only failures,
n=2: Progress output, n=3: Include commands called (default),
n=4: Include perf test results unconditionally,
n=5: Echo commands in subsidiary make invocations
diff --git a/testsuite/tests/gadt/T9380.hs b/testsuite/tests/gadt/T9380.hs
index ebc02178f1..99dfab8477 100644
--- a/testsuite/tests/gadt/T9380.hs
+++ b/testsuite/tests/gadt/T9380.hs
@@ -63,6 +63,6 @@ test2 =
V1a{} -> putStrLn "test2 - O_o"
main = do
- test0 -- no ouput at all
+ test0 -- no output at all
test1 -- A
test2 -- O_o \ No newline at end of file
diff --git a/testsuite/tests/partial-sigs/should_fail/PatBind3.hs b/testsuite/tests/partial-sigs/should_fail/PatBind3.hs
index 6da898bc09..23d74e6bfa 100644
--- a/testsuite/tests/partial-sigs/should_fail/PatBind3.hs
+++ b/testsuite/tests/partial-sigs/should_fail/PatBind3.hs
@@ -1,6 +1,6 @@
{-# LANGUAGE PartialTypeSignatures #-}
module PatBind3 where
--- Oddly GHC 8.0 accepted this, but it should obvoiusly fail!
+-- Oddly GHC 8.0 accepted this, but it should obviously fail!
foo :: (Bool, _) -> Char
Just foo = Just id
diff --git a/testsuite/tests/pmcheck/complete_sigs/completesig10.hs b/testsuite/tests/pmcheck/complete_sigs/completesig10.hs
index 66c446b6ef..4dbb26fed9 100644
--- a/testsuite/tests/pmcheck/complete_sigs/completesig10.hs
+++ b/testsuite/tests/pmcheck/complete_sigs/completesig10.hs
@@ -20,7 +20,7 @@ m2 :: T -> ()
m2 B = ()
m2 D = ()
--- Redudant incomplete overlap
+-- Redundant incomplete overlap
m3 :: T -> ()
m3 B = ()
m3 C = ()
diff --git a/testsuite/tests/simplStg/should_run/T13536.hs b/testsuite/tests/simplStg/should_run/T13536.hs
index cf70f46163..09daa73af4 100644
--- a/testsuite/tests/simplStg/should_run/T13536.hs
+++ b/testsuite/tests/simplStg/should_run/T13536.hs
@@ -8,7 +8,7 @@ unId False (Just (Id x)) = (Just x)
unId False Nothing = Nothing
{-# NOINLINE unId #-}
-val n = trace "evalued once, as it should" (Just (Id n))
+val n = trace "evaluated once, as it should" (Just (Id n))
{-# NOINLINE val #-}
foo b n = unId b (val n)
diff --git a/testsuite/tests/simplStg/should_run/T13536.stderr b/testsuite/tests/simplStg/should_run/T13536.stderr
index 638b7f82c1..4d6b00cfb5 100644
--- a/testsuite/tests/simplStg/should_run/T13536.stderr
+++ b/testsuite/tests/simplStg/should_run/T13536.stderr
@@ -1 +1 @@
-evalued once, as it should
+evaluated once, as it should