summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/coreSyn/CoreSubst.hs2
-rw-r--r--compiler/coreSyn/CoreUnfold.hs2
-rw-r--r--compiler/coreSyn/MkCore.hs2
-rw-r--r--compiler/ghci/ByteCodeGen.hs2
-rw-r--r--compiler/parser/Lexer.x2
-rw-r--r--compiler/simplCore/CallArity.hs2
-rw-r--r--compiler/simplCore/OccurAnal.hs2
-rw-r--r--compiler/simplCore/SetLevels.hs2
-rw-r--r--compiler/specialise/SpecConstr.hs2
-rw-r--r--compiler/typecheck/TcExpr.hs2
-rw-r--r--compiler/types/TyCoRep.hs4
-rw-r--r--docs/stg-spec/stg-spec.mng2
-rw-r--r--docs/users_guide/glasgow_exts.rst2
-rw-r--r--testsuite/tests/primops/should_run/T7689.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/tc195.hs2
-rw-r--r--testsuite/tests/warnings/should_compile/T11128.hs2
-rw-r--r--testsuite/tests/warnings/should_compile/T11128b.hs2
17 files changed, 18 insertions, 18 deletions
diff --git a/compiler/coreSyn/CoreSubst.hs b/compiler/coreSyn/CoreSubst.hs
index b4edfee593..4438d2b694 100644
--- a/compiler/coreSyn/CoreSubst.hs
+++ b/compiler/coreSyn/CoreSubst.hs
@@ -747,7 +747,7 @@ substTickish _subst other = other
{- Note [Substitute lazily]
~~~~~~~~~~~~~~~~~~~~~~~~~~~
-The functions that substitute over IdInfo must be pretty lazy, becuause
+The functions that substitute over IdInfo must be pretty lazy, because
they are knot-tied by substRecBndrs.
One case in point was Trac #10627 in which a rule for a function 'f'
diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs
index 7dde2c0edc..27045ff89a 100644
--- a/compiler/coreSyn/CoreUnfold.hs
+++ b/compiler/coreSyn/CoreUnfold.hs
@@ -785,7 +785,7 @@ buildSize :: ExprSize
buildSize = SizeIs 0 emptyBag 40
-- We really want to inline applications of build
-- build t (\cn -> e) should cost only the cost of e (because build will be inlined later)
- -- Indeed, we should add a result_discount becuause build is
+ -- Indeed, we should add a result_discount because build is
-- very like a constructor. We don't bother to check that the
-- build is saturated (it usually is). The "-2" discounts for the \c n,
-- The "4" is rather arbitrary.
diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs
index dbb3d451f1..ab4caf8601 100644
--- a/compiler/coreSyn/MkCore.hs
+++ b/compiler/coreSyn/MkCore.hs
@@ -327,7 +327,7 @@ Usually we want the former, but occasionally the latter.
mkCoreVarTup :: [Id] -> CoreExpr
mkCoreVarTup ids = mkCoreTup (map Var ids)
--- | Bulid the type of a small tuple that holds the specified variables
+-- | Build the type of a small tuple that holds the specified variables
-- One-tuples are flattened; see Note [Flattening of one-tuples]
mkCoreVarTupTy :: [Id] -> Type
mkCoreVarTupTy ids = mkBoxedTupleTy (map idType ids)
diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs
index da52b54240..fd186c7fe8 100644
--- a/compiler/ghci/ByteCodeGen.hs
+++ b/compiler/ghci/ByteCodeGen.hs
@@ -525,7 +525,7 @@ schemeE d s p (AnnCase scrut bndr _ [(DataAlt dc, [bind1, bind2], rhs)])
-- case .... of x { (# V'd-thing, a #) -> ... }
-- to
-- case .... of a { DEFAULT -> ... }
- -- becuse the return convention for both are identical.
+ -- because the return convention for both are identical.
--
-- Note that it does not matter losing the void-rep thing from the
-- envt (it won't be bound now) because we never look such things up.
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 4eb8fd35a2..d28d5847b6 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -526,7 +526,7 @@ $tab { warnTab }
-- expressions and patterns use the same parser, and also because we want
-- to allow type patterns within expression patterns.
--
--- Disambiguation is accomplished by requiring *something* to appear betwen
+-- Disambiguation is accomplished by requiring *something* to appear between
-- type application and the preceding token. This something must end with
-- a character that cannot be the end of the variable bound in an as-pattern.
-- Currently (June 2015), this means that the something cannot end with a
diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs
index bd997c3676..e172aefcd7 100644
--- a/compiler/simplCore/CallArity.hs
+++ b/compiler/simplCore/CallArity.hs
@@ -353,7 +353,7 @@ We never eta-expand a thunk in a recursive group, on the grounds that if it is
part of a recursive group, then it will be called multipe times.
This is not necessarily true, e.g. it would be safe to eta-expand t2 (but not
-t1) in the follwing code:
+t1) in the following code:
let go x = t1
t1 = if ... then t2 else ...
diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs
index 3eb20d0143..6628ee70ee 100644
--- a/compiler/simplCore/OccurAnal.hs
+++ b/compiler/simplCore/OccurAnal.hs
@@ -117,7 +117,7 @@ occurAnalyseExpr' enable_binder_swap expr
{- Note [Plugin rules]
~~~~~~~~~~~~~~~~~~~~~~
-Conal Eliot (Trac #11651) built a GHC plugin that added some
+Conal Elliott (Trac #11651) built a GHC plugin that added some
BuiltinRules (for imported Ids) to the mg_rules field of ModGuts, to
do some domain-specific transformations that could not be expressed
with an ordinary pattern-matching CoreRule. But then we can't extract
diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs
index e3ca7448a4..897b131d83 100644
--- a/compiler/simplCore/SetLevels.hs
+++ b/compiler/simplCore/SetLevels.hs
@@ -1146,7 +1146,7 @@ zap_demand_info v
Note [Zapping the demand info]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
VERY IMPORTANT: we must zap the demand info if the thing is going to
-float out, becuause it may be less demanded than at its original
+float out, because it may be less demanded than at its original
binding site. Eg
f :: Int -> Int
f x = let v = 3*4 in v+x
diff --git a/compiler/specialise/SpecConstr.hs b/compiler/specialise/SpecConstr.hs
index 218f8ce28e..5b8edb058e 100644
--- a/compiler/specialise/SpecConstr.hs
+++ b/compiler/specialise/SpecConstr.hs
@@ -1764,7 +1764,7 @@ Note [Strictness information in worker binders]
After having calculated the strictness annotation for the worker (see Note
[Transfer strictness] above), we also want to have this information attached to
the worker’s arguments, for the benefit of later passes. The function
-handOutStrictnessInformation decomposes the stricntess annotation calculated by
+handOutStrictnessInformation decomposes the strictness annotation calculated by
calcSpecStrictness and attaches them to the variables.
************************************************************************
diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs
index 3a8e82992b..af347d8d64 100644
--- a/compiler/typecheck/TcExpr.hs
+++ b/compiler/typecheck/TcExpr.hs
@@ -1214,7 +1214,7 @@ tcArgs fun orig_fun_ty fun_orig orig_args herald
tcArg :: LHsExpr Name -- The function (for error messages)
-> LHsExpr Name -- Actual arguments
-> TcRhoType -- expected arg type
- -> Int -- # of arugment
+ -> Int -- # of argument
-> TcM (LHsExpr TcId) -- Resulting argument
tcArg fun arg ty arg_no = addErrCtxt (funAppCtxt fun arg arg_no) $
tcPolyExprNC arg ty
diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs
index 46214e8634..d6f551614a 100644
--- a/compiler/types/TyCoRep.hs
+++ b/compiler/types/TyCoRep.hs
@@ -499,8 +499,8 @@ In type declarations:
* Invisible (k1), Specified (k)
data T a b (c :: k) = MkT (a b) (Proxy c)
Here T's kind is T :: forall {k1:*} (k:*). (k1->*) -> k1 -> k -> *
- So 'k' is Specified, becuase it appears explicitly,
- but 'k1' is Invisible, becuase it does not
+ So 'k' is Specified, because it appears explicitly,
+ but 'k1' is Invisible, because it does not
---- Printing -----
diff --git a/docs/stg-spec/stg-spec.mng b/docs/stg-spec/stg-spec.mng
index ce5ca3f40b..325410e218 100644
--- a/docs/stg-spec/stg-spec.mng
+++ b/docs/stg-spec/stg-spec.mng
@@ -139,7 +139,7 @@ application of a let-no-escape variable.
\gram{\ottret}
Values $v$ are functions (re-entrant closures) and constructors; thunks
-are not considered vaules. Evaluation guarantees that a value will be
+are not considered values. Evaluation guarantees that a value will be
produced.
Profiling also records allocation costs for creating objects on the heap:
diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index b828ef642c..220e642733 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -4301,7 +4301,7 @@ all currently bundled constructors. For example, we could write: ::
in which case, ``Example`` would export the type constructor ``MyNum`` with
the data constructor ``MkNum`` and also the pattern synonym ``Zero``.
-Bundled patterns synoyms are type checked to ensure that they are of the same
+Bundled patterns synonyms are type checked to ensure that they are of the same
type as the type constructor which they are bundled with. A pattern synonym
``P`` can not be bundled with a type constructor ``T`` if ``P``\'s type is visibly
incompatible with ``T``.
diff --git a/testsuite/tests/primops/should_run/T7689.hs b/testsuite/tests/primops/should_run/T7689.hs
index 12045474de..0c441e252e 100644
--- a/testsuite/tests/primops/should_run/T7689.hs
+++ b/testsuite/tests/primops/should_run/T7689.hs
@@ -53,7 +53,7 @@ main = do
-- anything xored with itself is 0
print (I# (maxI# `xorI#` maxI#) == 0)
print (I# (minI# `xorI#` minI#) == 0)
- -- xoring with -1 is like bitwise negation (becuse -1 has all bits set to 1)
+ -- xoring with -1 is like bitwise negation (because -1 has all bits set to 1)
print (I# (minI# `xorI#` -1#) == maxI)
print (I# (maxI# `xorI#` -1#) == minI)
print (I# (-1# `xorI#` minI#) == maxI)
diff --git a/testsuite/tests/typecheck/should_compile/tc195.hs b/testsuite/tests/typecheck/should_compile/tc195.hs
index 8eacf024ca..dd376a5d68 100644
--- a/testsuite/tests/typecheck/should_compile/tc195.hs
+++ b/testsuite/tests/typecheck/should_compile/tc195.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances, TypeSynonymInstances #-}
--- This one made GHC 6.4 loop becuause Unify.unify
+-- This one made GHC 6.4 loop because Unify.unify
-- didn't deal correctly with unifying
-- a :=: Foo a
-- where
diff --git a/testsuite/tests/warnings/should_compile/T11128.hs b/testsuite/tests/warnings/should_compile/T11128.hs
index 081e0748ea..23725c1e4b 100644
--- a/testsuite/tests/warnings/should_compile/T11128.hs
+++ b/testsuite/tests/warnings/should_compile/T11128.hs
@@ -35,7 +35,7 @@ instance M.Monad T1 where
(>>) = undefined
----------------------------------------------------------------------------
--- backward compat canonical defintion
+-- backward compat canonical definition
data T2 a = T2 a deriving Functor
diff --git a/testsuite/tests/warnings/should_compile/T11128b.hs b/testsuite/tests/warnings/should_compile/T11128b.hs
index 2cca9a53e0..497927716c 100644
--- a/testsuite/tests/warnings/should_compile/T11128b.hs
+++ b/testsuite/tests/warnings/should_compile/T11128b.hs
@@ -43,7 +43,7 @@ instance MF.MonadFail T1 where
fail = M.fail
----------------------------------------------------------------------------
--- backward compat canonical defintion
+-- backward compat canonical definition
data T2 a = T2 a deriving Functor