summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGabor Greif <ggreif@gmail.com>2019-01-22 12:07:47 +0100
committerBen Gamari <ben@well-typed.com>2019-01-23 14:07:28 -0500
commitbb2acfe0ec4c196a87218709ee28327845d62dc4 (patch)
tree5b7c314caa4944997e7faa51ba3fd9c5328fc913
parentc9a02dfc32ea4304c1c0d02bd8091fd5d045741f (diff)
downloadhaskell-bb2acfe0ec4c196a87218709ee28327845d62dc4.tar.gz
A few typofixes
-rw-r--r--compiler/basicTypes/BasicTypes.hs2
-rw-r--r--compiler/coreSyn/CoreArity.hs2
-rw-r--r--compiler/coreSyn/CoreSyn.hs2
-rw-r--r--compiler/coreSyn/CoreUnfold.hs2
-rw-r--r--compiler/hieFile/HieAst.hs2
-rw-r--r--compiler/hsSyn/HsDecls.hs2
-rw-r--r--compiler/main/InteractiveEval.hs2
-rw-r--r--compiler/nativeGen/CFG.hs2
-rw-r--r--compiler/prelude/primops.txt.pp2
-rw-r--r--compiler/simplCore/Simplify.hs5
-rw-r--r--compiler/stgSyn/CoreToStg.hs2
-rw-r--r--compiler/typecheck/FamInst.hs2
-rw-r--r--docs/users_guide/extending_ghc.rst2
-rw-r--r--hadrian/src/Rules/Documentation.hs2
-rw-r--r--libraries/base/Data/Either.hs4
-rw-r--r--libraries/base/Data/Foldable.hs2
-rw-r--r--rts/posix/Signals.c2
17 files changed, 19 insertions, 20 deletions
diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index 200e5c9b8a..ded9c0d9cf 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -1277,7 +1277,7 @@ The main effects of CONLIKE are:
- The occurrence analyser (OccAnal) and simplifier (Simplify) treat
CONLIKE thing like constructors, by ANF-ing them
- - New function coreUtils.exprIsExpandable is like exprIsCheap, but
+ - New function CoreUtils.exprIsExpandable is like exprIsCheap, but
additionally spots applications of CONLIKE functions
- A CoreUnfolding has a field that caches exprIsExpandable
diff --git a/compiler/coreSyn/CoreArity.hs b/compiler/coreSyn/CoreArity.hs
index d15da87aac..2947518352 100644
--- a/compiler/coreSyn/CoreArity.hs
+++ b/compiler/coreSyn/CoreArity.hs
@@ -598,7 +598,7 @@ The analysis is easy to achieve because exprEtaExpandArity takes an
argument
type CheapFun = CoreExpr -> Maybe Type -> Bool
used to decide if an expression is cheap enough to push inside a
-lambda. And exprIsCheap' in turn takes an argument
+lambda. And exprIsCheapX in turn takes an argument
type CheapAppFun = Id -> Int -> Bool
which tells when an application is cheap. This makes it easy to
write the analysis loop.
diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs
index 53a399204e..c4fedbbad7 100644
--- a/compiler/coreSyn/CoreSyn.hs
+++ b/compiler/coreSyn/CoreSyn.hs
@@ -509,7 +509,7 @@ this exhaustive list can be empty!
scrutinee is bound to raise an exception or diverge. When do we know
this? See Note [Bottoming expressions] in CoreUtils.
-* The possiblity of empty alternatives is one reason we need a type on
+* The possibility of empty alternatives is one reason we need a type on
the case expression: if the alternatives are empty we can't get the
type from the alternatives!
diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs
index 020aa8525a..11c2a7533e 100644
--- a/compiler/coreSyn/CoreUnfold.hs
+++ b/compiler/coreSyn/CoreUnfold.hs
@@ -294,7 +294,7 @@ Note [INLINE pragmas and boring contexts]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
An INLINE pragma uses mkInlineUnfoldingWithArity to build the
unfolding. That sets the ug_boring_ok flag to False if the function
-is not tiny (inlineBorkingOK), so that even INLINE functions are not
+is not tiny (inlineBoringOK), so that even INLINE functions are not
inlined in an utterly boring context. E.g.
\x y. Just (f y x)
Nothing is gained by inlining f here, even if it has an INLINE
diff --git a/compiler/hieFile/HieAst.hs b/compiler/hieFile/HieAst.hs
index 432dc36069..401b861e30 100644
--- a/compiler/hieFile/HieAst.hs
+++ b/compiler/hieFile/HieAst.hs
@@ -210,7 +210,7 @@ data PScoped a = PS (Maybe Span)
{- Note [TyVar Scopes]
Due to -XScopedTypeVariables, type variables can be in scope quite far from
their original binding. We resolve the scope of these type variables
-in a seperate pass
+in a separate pass
-}
data TScoped a = TS TyVarScope a -- TyVarScope
diff --git a/compiler/hsSyn/HsDecls.hs b/compiler/hsSyn/HsDecls.hs
index 2b8c16311d..5b06db8c02 100644
--- a/compiler/hsSyn/HsDecls.hs
+++ b/compiler/hsSyn/HsDecls.hs
@@ -796,7 +796,7 @@ Examples:
* data T2 a b = ...
-- No CUSK; we do not want to guess T2 :: * -> * -> *
- -- becuase the full decl might be data T a b = MkT (a b)
+ -- because the full decl might be data T a b = MkT (a b)
* data T3 (a :: k -> *) (b :: *) = ...
-- CUSK; equivalent to T3 :: (k -> *) -> * -> *
diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs
index ad3c500d1f..79e64b3ad9 100644
--- a/compiler/main/InteractiveEval.hs
+++ b/compiler/main/InteractiveEval.hs
@@ -246,7 +246,7 @@ runParsedDecls decls = do
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We don't want to display internally-generated bindings to users.
Things like the coercion axiom for newtypes. These bindings all get
-OccNames that users can't write, to avoid the possiblity of name
+OccNames that users can't write, to avoid the possibility of name
clashes (in linker symbols). That gives a convenient way to suppress
them. The relevant predicate is OccName.isDerivedOccName.
See Trac #11051 for more background and examples.
diff --git a/compiler/nativeGen/CFG.hs b/compiler/nativeGen/CFG.hs
index b5b0fd7ca9..b19db02b13 100644
--- a/compiler/nativeGen/CFG.hs
+++ b/compiler/nativeGen/CFG.hs
@@ -361,7 +361,7 @@ pprEdgeWeights m =
ppr weight <> text "\"];\n"
--for the case that there are no edges from/to this node.
--This should rarely happen but it can save a lot of time
- --to immediatly see it when it does.
+ --to immediately see it when it does.
printNode node
= text "\t" <> ppr node <> text ";\n"
getEdgeNodes (from, to, _weight) = [from,to]
diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp
index eb635fb215..8904bbcec5 100644
--- a/compiler/prelude/primops.txt.pp
+++ b/compiler/prelude/primops.txt.pp
@@ -21,7 +21,7 @@
-- http://ghc.haskell.org/trac/ghc/wiki/Commentary/PrimOps
--
-- Note in particular that Haskell block-style comments are not recognized
--- here, so stick to '--' (even for Notes spanning mutliple lines).
+-- here, so stick to '--' (even for Notes spanning multiple lines).
-- This file is divided into named sections, each containing or more
-- primop entries. Section headers have the format:
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index fca9904f19..51e1d7de5e 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -255,7 +255,7 @@ simplLazyBind env top_lvl is_rec bndr bndr1 rhs rhs_se
| not (tickishFloatable t) = surely_not_lam e
-- eta-reduction could float
surely_not_lam _ = True
- -- Do not do the "abstract tyyvar" thing if there's
+ -- Do not do the "abstract tyvar" thing if there's
-- a lambda inside, because it defeats eta-reduction
-- f = /\a. \x. g a x
-- should eta-reduce.
@@ -270,7 +270,7 @@ simplLazyBind env top_lvl is_rec bndr bndr1 rhs rhs_se
-- Never float join-floats out of a non-join let-binding
-- So wrap the body in the join-floats right now
- -- Henc: body_floats1 consists only of let-floats
+ -- Hence: body_floats1 consists only of let-floats
; let (body_floats1, body1) = wrapJoinFloatsX body_floats0 body0
-- ANF-ise a constructor or PAP rhs
@@ -3560,4 +3560,3 @@ simplRules env mb_new_id rules mb_cont
, ru_fn = fn_name'
, ru_args = args'
, ru_rhs = rhs' }) }
-
diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs
index 573db78a06..e8f159b569 100644
--- a/compiler/stgSyn/CoreToStg.hs
+++ b/compiler/stgSyn/CoreToStg.hs
@@ -180,7 +180,7 @@ import Control.Monad (liftM, ap)
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
--
-- Previously `coreToStg` was initializing cost-centre stack fields as `noCCS`,
--- and the fields were then fixed by a seperate pass `stgMassageForProfiling`.
+-- and the fields were then fixed by a separate pass `stgMassageForProfiling`.
-- We now initialize these correctly. The initialization works like this:
--
-- - For non-top level bindings always use `currentCCS`.
diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs
index 5ad27db06e..aec8e4153f 100644
--- a/compiler/typecheck/FamInst.hs
+++ b/compiler/typecheck/FamInst.hs
@@ -776,7 +776,7 @@ unusedInjTvsInRHS tycon injList lhs rhs =
(`minusVarSet` injRhsVars) <$> injLHSVars
where
inj_pairs :: [(Type, ArgFlag)]
- -- All the injective arguments, paired with their visiblity
+ -- All the injective arguments, paired with their visibility
inj_pairs = ASSERT2( injList `equalLength` lhs
, ppr tycon $$ ppr injList $$ ppr lhs )
filterByList injList (lhs `zip` tyConArgFlags tycon lhs)
diff --git a/docs/users_guide/extending_ghc.rst b/docs/users_guide/extending_ghc.rst
index 02847c9b86..04bb2dfb1e 100644
--- a/docs/users_guide/extending_ghc.rst
+++ b/docs/users_guide/extending_ghc.rst
@@ -671,7 +671,7 @@ you need to access the renamed or type checked version of the syntax tree with
renamed :: [CommandLineOption] -> TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn)
By overriding the ``renamedResultAction`` field we can modify each ``HsGroup``
-after it has been renamed. A source file is seperated into groups depending on
+after it has been renamed. A source file is separated into groups depending on
the location of template haskell splices so the contents of these groups may
not be intuitive. In order to save the entire renamed AST for inspection
at the end of typechecking you can set ``renamedResultAction`` to ``keepRenamedSource``
diff --git a/hadrian/src/Rules/Documentation.hs b/hadrian/src/Rules/Documentation.hs
index 954264aa28..2d7a4b1ef7 100644
--- a/hadrian/src/Rules/Documentation.hs
+++ b/hadrian/src/Rules/Documentation.hs
@@ -118,7 +118,7 @@ buildLibraryDocumentation = do
-- We want Haddocks for everything except `rts` to be built, but we
-- don't want the index to be polluted by stuff from `ghc`-the-library
- -- (there will be a seperate top-level link to those Haddocks).
+ -- (there will be a separate top-level link to those Haddocks).
haddocks <- allHaddocks
let neededDocs = filter (\x -> takeFileName x /= "rts.haddock") haddocks
libDocs = filter (\x -> takeFileName x /= "ghc.haddock") neededDocs
diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs
index 58987a3910..afd676d415 100644
--- a/libraries/base/Data/Either.hs
+++ b/libraries/base/Data/Either.hs
@@ -192,7 +192,7 @@ either _ g (Right y) = g y
--
lefts :: [Either a b] -> [a]
lefts x = [a | Left a <- x]
-{-# INLINEABLE lefts #-} -- otherwise doesnt get an unfolding, see #13689
+{-# INLINEABLE lefts #-} -- otherwise doesn't get an unfolding, see #13689
-- | Extracts from a list of 'Either' all the 'Right' elements.
-- All the 'Right' elements are extracted in order.
@@ -207,7 +207,7 @@ lefts x = [a | Left a <- x]
--
rights :: [Either a b] -> [b]
rights x = [a | Right a <- x]
-{-# INLINEABLE rights #-} -- otherwise doesnt get an unfolding, see #13689
+{-# INLINEABLE rights #-} -- otherwise doesn't get an unfolding, see #13689
-- | Partitions a list of 'Either' into two lists.
-- All the 'Left' elements are extracted, in order, to the first
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index a7d57f7e62..9a031212f0 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -706,7 +706,7 @@ GHC used to proceed like this:
mapM_ <big> (build g)
- = { Defintion of mapM_ }
+ = { Definition of mapM_ }
foldr ((>>) . <big>) (return ()) (build g)
= { foldr/build rule }
diff --git a/rts/posix/Signals.c b/rts/posix/Signals.c
index f033870d16..f8bd9fb829 100644
--- a/rts/posix/Signals.c
+++ b/rts/posix/Signals.c
@@ -164,7 +164,7 @@ ioManagerWakeup (void)
r = write(io_manager_wakeup_fd, &byte, 1);
#endif
/* N.B. If the TimerManager is shutting down as we run this
- * then there is a possiblity that our first read of
+ * then there is a possibility that our first read of
* io_manager_wakeup_fd is non-negative, but before we get to the
* write the file is closed. If this occurs, io_manager_wakeup_fd
* will be written into with -1 (GHC.Event.Control does this prior