summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGabor Greif <ggreif@gmail.com>2016-12-01 17:46:35 (GMT)
committerGabor Greif <ggreif@gmail.com>2016-12-01 18:38:09 (GMT)
commit0f37550c797b08b953049fb84f6ea127e4d7668c (patch)
treeec45e3a68b038e6c9f88263769da3d82ff1d14f2
parent6576bf83cdf4eac05eb88a24aa934a736c91e3da (diff)
downloadghc-0f37550c797b08b953049fb84f6ea127e4d7668c.zip
ghc-0f37550c797b08b953049fb84f6ea127e4d7668c.tar.gz
ghc-0f37550c797b08b953049fb84f6ea127e4d7668c.tar.bz2
Typos in comments
-rw-r--r--compiler/coreSyn/MkCore.hs2
-rw-r--r--compiler/main/DynFlags.hs4
-rw-r--r--compiler/main/HeaderInfo.hs2
-rw-r--r--compiler/typecheck/TcDeriv.hs2
-rw-r--r--compiler/typecheck/TcFlatten.hs2
-rw-r--r--compiler/typecheck/TcSMonad.hs2
-rw-r--r--libraries/base/Control/Exception.hs2
-rw-r--r--libraries/base/tests/unicode001.hs2
-rw-r--r--libraries/integer-gmp/src/GHC/Integer/Type.hs2
-rw-r--r--testsuite/tests/simplCore/should_run/simplrun007.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T12427a.hs2
-rw-r--r--testsuite/tests/typecheck/should_compile/T2357.hs2
12 files changed, 13 insertions, 13 deletions
diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs
index e7fc7f9..77027fc 100644
--- a/compiler/coreSyn/MkCore.hs
+++ b/compiler/coreSyn/MkCore.hs
@@ -750,7 +750,7 @@ mkRuntimeErrorId name
'error' and 'undefined' have types
error :: forall (v :: RuntimeRep) (a :: TYPE v). String -> a
undefined :: forall (v :: RuntimeRep) (a :: TYPE v). a
-Notice the runtime-representation polymophism. This ensures that
+Notice the runtime-representation polymorphism. This ensures that
"error" can be instantiated at unboxed as well as boxed types.
This is OK because it never returns, so the return type is irrelevant.
-}
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 30bfa5e..cbf247c 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -893,7 +893,7 @@ data DynFlags = DynFlags {
nextWrapperNum :: IORef (ModuleEnv Int),
- -- | Machine dependant flags (-m<blah> stuff)
+ -- | Machine dependent flags (-m<blah> stuff)
sseVersion :: Maybe SseVersion,
avx :: Bool,
avx2 :: Bool,
@@ -2969,7 +2969,7 @@ dynamic_flags_deps = [
(NoArg (setGeneralFlag Opt_NoLlvmMangler)) -- hidden flag
, make_ord_flag defGhcFlag "ddump-debug" (setDumpFlag Opt_D_dump_debug)
- ------ Machine dependant (-m<blah>) stuff ---------------------------
+ ------ Machine dependent (-m<blah>) stuff ---------------------------
, make_ord_flag defGhcFlag "msse" (noArg (\d ->
d { sseVersion = Just SSE1 }))
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index 5c8c893..2c27de1 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -97,7 +97,7 @@ mkPrelImports :: ModuleName
-> SrcSpan -- Attribute the "import Prelude" to this location
-> Bool -> [LImportDecl RdrName]
-> [LImportDecl RdrName]
--- Consruct the implicit declaration "import Prelude" (or not)
+-- Construct the implicit declaration "import Prelude" (or not)
--
-- NB: opt_NoImplicitPrelude is slightly different to import Prelude ();
-- because the former doesn't even look at Prelude.hi for instance
diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs
index 7c1857a..f3b5e6a 100644
--- a/compiler/typecheck/TcDeriv.hs
+++ b/compiler/typecheck/TcDeriv.hs
@@ -368,7 +368,7 @@ Consider this (see Trac #1954):
newtype P a = MkP (IO a) deriving Monad
If you compile with -Wunused-binds you do not expect the warning
-"Defined but not used: data consructor MkP". Yet the newtype deriving
+"Defined but not used: data constructor MkP". Yet the newtype deriving
code does not explicitly mention MkP, but it should behave as if you
had written
instance Monad P where
diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs
index 4fc8414..94fdfb8 100644
--- a/compiler/typecheck/TcFlatten.hs
+++ b/compiler/typecheck/TcFlatten.hs
@@ -1322,7 +1322,7 @@ It is easy to implement, in TcInteract.kick_out, by only kicking out an inert
only if (a) the work item can rewrite the inert AND
(b) the inert cannot rewrite the work item
-This is signifcantly harder to think about. It can save a LOT of work
+This is significantly harder to think about. It can save a LOT of work
in occurs-check cases, but we don't care about them much. Trac #5837
is an example; all the constraints here are Givens
diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs
index cff667e..1f1705d 100644
--- a/compiler/typecheck/TcSMonad.hs
+++ b/compiler/typecheck/TcSMonad.hs
@@ -1155,7 +1155,7 @@ Note [Do not do improvement for WOnly]
We do improvement between two constraints (e.g. for injectivity
or functional dependencies) only if both are "improvable". And
we improve a constraint wrt the top-level instances only if
-it is improveable.
+it is improvable.
Improvable: [G] [WD] [D}
Not improvable: [W]
diff --git a/libraries/base/Control/Exception.hs b/libraries/base/Control/Exception.hs
index cf52d1d..a6c1083 100644
--- a/libraries/base/Control/Exception.hs
+++ b/libraries/base/Control/Exception.hs
@@ -305,7 +305,7 @@ exceptions is that they normally can occur anywhere, but within a
interruptible (or call other interruptible operations). In many cases
these operations may themselves raise exceptions, such as I\/O errors,
so the caller will usually be prepared to handle exceptions arising from the
-operation anyway. To perfom an explicit poll for asynchronous exceptions
+operation anyway. To perform an explicit poll for asynchronous exceptions
inside 'mask', use 'allowInterrupt'.
Sometimes it is too onerous to handle exceptions in the middle of a
diff --git a/libraries/base/tests/unicode001.hs b/libraries/base/tests/unicode001.hs
index ceac9a5..d5f6135 100644
--- a/libraries/base/tests/unicode001.hs
+++ b/libraries/base/tests/unicode001.hs
@@ -1,4 +1,4 @@
--- !!! Tests the various character classifiactions for a selection of Unicode
+-- !!! Tests the various character classifications for a selection of Unicode
-- characters.
module Main where
diff --git a/libraries/integer-gmp/src/GHC/Integer/Type.hs b/libraries/integer-gmp/src/GHC/Integer/Type.hs
index 6506ebf..9800f55 100644
--- a/libraries/integer-gmp/src/GHC/Integer/Type.hs
+++ b/libraries/integer-gmp/src/GHC/Integer/Type.hs
@@ -1793,7 +1793,7 @@ byteArrayToBigNat# ba# n0#
n# = fmssl (n0# -# 1#)
- -- find most signifcant set limb, return normalized size
+ -- find most significant set limb, return normalized size
fmssl i#
| isTrue# (i# <# 0#) = 0#
| isTrue# (neWord# (indexWordArray# ba# i#) 0##) = i# +# 1#
diff --git a/testsuite/tests/simplCore/should_run/simplrun007.hs b/testsuite/tests/simplCore/should_run/simplrun007.hs
index 12bfb2d..9cf3760 100644
--- a/testsuite/tests/simplCore/should_run/simplrun007.hs
+++ b/testsuite/tests/simplCore/should_run/simplrun007.hs
@@ -15,7 +15,7 @@ main = do phex (I# (uncheckedIShiftL# (negateInt# 5#) 2#))
phex x = putStrLn (showSigned (\x -> ("0x"++) . showHex x) 0 x "")
-{- Too wordsize-dependant
+{- Too wordsize-dependent
phex x = putStrLn (hex x)
hex x = "0x" ++ [onedigit (fromIntegral ((x `shiftR` (i*4)) .&. 0xF))
| i <- [digits-1,digits-2..0]]
diff --git a/testsuite/tests/typecheck/should_compile/T12427a.hs b/testsuite/tests/typecheck/should_compile/T12427a.hs
index 1cbf7c5..cffab89 100644
--- a/testsuite/tests/typecheck/should_compile/T12427a.hs
+++ b/testsuite/tests/typecheck/should_compile/T12427a.hs
@@ -20,7 +20,7 @@ h11 y = case y of T1 _ v -> v
-- Failed in 8.0.1
-- Succeeds in 8.2 because the pattern match has
-- no existentials, so it doesn't matter than
--- v is polymoprhic
+-- v is polymorphic
h12 y = case y of T2 v -> v
-- Inference
diff --git a/testsuite/tests/typecheck/should_compile/T2357.hs b/testsuite/tests/typecheck/should_compile/T2357.hs
index 61d95f1..be297e0 100644
--- a/testsuite/tests/typecheck/should_compile/T2357.hs
+++ b/testsuite/tests/typecheck/should_compile/T2357.hs
@@ -4,7 +4,7 @@ module Foo where
f :: Read a => a
-- This one needs NoMonomorphismRestriction else f could
--- not get a polymoprhic type
+-- not get a polymorphic type
(f, _) = (read "3", True)
g :: Read a => a