summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/basicTypes/DataCon.hs2
-rw-r--r--compiler/hsSyn/HsExpr.hs2
-rw-r--r--compiler/main/GhcMake.hs2
-rw-r--r--compiler/typecheck/TcBinds.hs6
-rw-r--r--compiler/typecheck/TcDeriv.hs2
-rw-r--r--compiler/typecheck/TcForeign.hs2
-rw-r--r--compiler/typecheck/TcSMonad.hs2
-rw-r--r--compiler/types/Type.hs2
-rw-r--r--docs/users_guide/glasgow_exts.rst2
-rw-r--r--libraries/base/GHC/IO/Encoding/Types.hs2
-rw-r--r--testsuite/tests/safeHaskell/check/all.T4
-rw-r--r--testsuite/tests/typecheck/should_compile/T9708.hs2
-rw-r--r--testsuite/tests/typecheck/should_fail/ContextStack2.hs4
13 files changed, 17 insertions, 17 deletions
diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs
index 9a827e03ee..6e69a1cbce 100644
--- a/compiler/basicTypes/DataCon.hs
+++ b/compiler/basicTypes/DataCon.hs
@@ -1079,7 +1079,7 @@ dataConCannotMatch tys con
* *
Promotion
- These functions are here becuase
+ These functions are here because
- isPromotableTyCon calls dataConFullSig
- mkDataCon calls promoteType
- It's nice to keep the promotion stuff together
diff --git a/compiler/hsSyn/HsExpr.hs b/compiler/hsSyn/HsExpr.hs
index 127d87a3ec..b15e4304f4 100644
--- a/compiler/hsSyn/HsExpr.hs
+++ b/compiler/hsSyn/HsExpr.hs
@@ -1642,7 +1642,7 @@ pprStmt (ApplicativeStmt args mb_join _)
-- of statements.
pp_for_user = vcat $ punctuate semi $ concatMap flattenArg args
- -- ppr directly rather than transforming here, becuase we need to
+ -- ppr directly rather than transforming here, because we need to
-- inject a "return" which is hard when we're polymorphic in the id
-- type.
flattenStmt :: ExprLStmt idL -> [SDoc]
diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs
index 06cd082d13..d390c16817 100644
--- a/compiler/main/GhcMake.hs
+++ b/compiler/main/GhcMake.hs
@@ -739,7 +739,7 @@ parUpsweep n_jobs old_hpt stable_mods cleanup sccs = do
hsc_env_var <- liftIO $ newMVar hsc_env
-- The old HPT is used for recompilation checking in upsweep_mod. When a
- -- module sucessfully gets compiled, its HMI is pruned from the old HPT.
+ -- module successfully gets compiled, its HMI is pruned from the old HPT.
old_hpt_var <- liftIO $ newIORef old_hpt
-- What we use to limit parallelism with.
diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index 96aec1eefe..673109b126 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -293,7 +293,7 @@ Consider this (Trac #9161)
Here, the type signature for b mentions A. But A is a pattern
synonym, which is typechecked (for very good reasons; a view pattern
in the RHS may mention a value binding) as part of a group of
-bindings. It is entirely resonable to reject this, but to do so
+bindings. It is entirely reasonable to reject this, but to do so
we need A to be in the kind environment when kind-checking the signature for B.
Hence the tcExtendKindEnv2 patsyn_placeholder_kinds, which adds a binding
@@ -754,7 +754,7 @@ mkInferredPolyId qtvs inferred_theta poly_name mb_sig mono_ty
-- Example: f :: [F Int] -> Bool
-- should be rewritten to f :: [Char] -> Bool, if possible
--
- -- We can discard the coercion _co, becuase we'll reconstruct
+ -- We can discard the coercion _co, because we'll reconstruct
-- it in the call to tcSubType below
; (my_tvs, theta') <- chooseInferredQuantifiers
@@ -1770,7 +1770,7 @@ tcUserTypeSig hs_sig_ty mb_name
-- Check for validity (eg rankN etc)
-- The ambiguity check will happen (from checkValidType),
- -- but unnecessarily; it will always succeed becuase there
+ -- but unnecessarily; it will always succeed because there
-- is no quantification
; _ <- zonkAndCheckValidity ctxt_F (mkPhiTy theta tau)
diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs
index aab1e4d08b..107648dbb9 100644
--- a/compiler/typecheck/TcDeriv.hs
+++ b/compiler/typecheck/TcDeriv.hs
@@ -1135,7 +1135,7 @@ canDeriveAnyClass dflags _tycon clas
where
-- We are making an instance (C t1 .. tn (T s1 .. sm))
-- and we can only do so if the kind of C's last argument
- -- is * or (* -> *). Becuase only then can we make a resonable
+ -- is * or (* -> *). Because only then can we make a reasonable
-- guess at the instance context
target_kind = tyVarKind (last (classTyVars clas))
diff --git a/compiler/typecheck/TcForeign.hs b/compiler/typecheck/TcForeign.hs
index 897f5d6c6f..01be9204bb 100644
--- a/compiler/typecheck/TcForeign.hs
+++ b/compiler/typecheck/TcForeign.hs
@@ -466,7 +466,7 @@ checkForeignRes non_io_result_ok check_safe pred_res_ty ty
_ | check_safe && safeLanguageOn dflags
-> addErrTc (illegalForeignTyErr result safeHsErr)
- -- sucess! non-IO return is fine
+ -- success! non-IO return is fine
_ -> return () }
where
safeHsErr = ptext $ sLit "Safe Haskell is on, all FFI imports must be in the IO monad"
diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs
index 0c5564b413..d9c56382a6 100644
--- a/compiler/typecheck/TcSMonad.hs
+++ b/compiler/typecheck/TcSMonad.hs
@@ -2618,7 +2618,7 @@ sites. Not only do we want an error message for each, but with
*derived* insolubles, we only want to report each one once. Why?
(a) A constraint (C r s t) where r -> s, say, may generate the same fundep
- equality many times, as the original constraint is sucessively rewritten.
+ equality many times, as the original constraint is successively rewritten.
(b) Ditto the successive iterations of the main solver itself, as it traverses
the constraint tree. See example below.
diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index 78c1670f74..50d3a7e2c3 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -838,7 +838,7 @@ splitForAllTy_maybe ty = splitFAT_m ty
splitFAT_m _ = Nothing
-- | Attempts to take a forall type apart, returning all the immediate such bound
--- type variables and the remainder of the type. Always suceeds, even if that means
+-- type variables and the remainder of the type. Always succeeds, even if that means
-- returning an empty list of 'TyVar's
splitForAllTys :: Type -> ([TyVar], Type)
splitForAllTys ty = split ty ty []
diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst
index 51ac12a5fc..0959337ddc 100644
--- a/docs/users_guide/glasgow_exts.rst
+++ b/docs/users_guide/glasgow_exts.rst
@@ -4490,7 +4490,7 @@ Deriving any other class
With ``-XDeriveAnyClass`` you can derive any other class. The compiler
will simply generate an instance declaration with no explicitly-defined
-mathods.
+methods.
This is
mostly useful in classes whose `minimal set <#minimal-pragma>`__ is
empty, and especially when writing
diff --git a/libraries/base/GHC/IO/Encoding/Types.hs b/libraries/base/GHC/IO/Encoding/Types.hs
index 02a0d13e8b..cf32d7f86f 100644
--- a/libraries/base/GHC/IO/Encoding/Types.hs
+++ b/libraries/base/GHC/IO/Encoding/Types.hs
@@ -123,7 +123,7 @@ instance Show TextEncoding where
-- | @since 4.4.0.0
data CodingProgress = InputUnderflow -- ^ Stopped because the input contains insufficient available elements,
- -- or all of the input sequence has been sucessfully translated.
+ -- or all of the input sequence has been successfully translated.
| OutputUnderflow -- ^ Stopped because the output contains insufficient free elements
| InvalidSequence -- ^ Stopped because there are sufficient free elements in the output
-- to output at least one encoded ASCII character, but the input contains
diff --git a/testsuite/tests/safeHaskell/check/all.T b/testsuite/tests/safeHaskell/check/all.T
index 0a4fda62c8..fb2841b73c 100644
--- a/testsuite/tests/safeHaskell/check/all.T
+++ b/testsuite/tests/safeHaskell/check/all.T
@@ -18,13 +18,13 @@ test('Check01', normal, multi_compile_fail, ['Check01 -distrust base', [
('Check01_B.hs', '-trust base')
], '-fpackage-trust'])
-# suceed this time since we trust base when we compile AND use CheckB
+# succeed this time since we trust base when we compile AND use CheckB
test('Check02', normal, multi_compile, ['Check02', [
('Check02_A.hs', ''),
('Check02_B.hs', '')
], '-trust base -fpackage-trust'])
-# suceed as while like Check01_fail we don't import CheckB as a safe
+# succeed as while like Check01_fail we don't import CheckB as a safe
# import this time, so don't require base trusted when used.
test('Check03', normal, multi_compile, ['Check03', [
('Check03_A.hs', ''),
diff --git a/testsuite/tests/typecheck/should_compile/T9708.hs b/testsuite/tests/typecheck/should_compile/T9708.hs
index 61928d41ad..cb0e8474c3 100644
--- a/testsuite/tests/typecheck/should_compile/T9708.hs
+++ b/testsuite/tests/typecheck/should_compile/T9708.hs
@@ -6,7 +6,7 @@ import Data.Proxy
type family SomeFun (n :: Nat)
--- See the Trac ticket; whether this suceeds or fails is distintly random
+-- See the Trac ticket; whether this succeeds or fails is distinctly random
-- upon creation, commit f861fc6ad8e5504a4fecfc9bb0945fe2d313687c, this failed
diff --git a/testsuite/tests/typecheck/should_fail/ContextStack2.hs b/testsuite/tests/typecheck/should_fail/ContextStack2.hs
index 71d22c3241..f3f93eb912 100644
--- a/testsuite/tests/typecheck/should_fail/ContextStack2.hs
+++ b/testsuite/tests/typecheck/should_fail/ContextStack2.hs
@@ -22,7 +22,7 @@ t = undefined
* fsk ~ (TF a, TF Int)
(flatten lhs)
a ~ (TF a, TF Int)
- (flaten rhs)
+ (flatten rhs)
a ~ (fsk1, TF Int)
(wk) TF a ~ fsk1
@@ -50,4 +50,4 @@ t = undefined
(wk) TF Int ~ fsk2
TF fsk1 ~ fsk3
--} \ No newline at end of file
+-}