summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/basicTypes/NameEnv.hs2
-rw-r--r--compiler/coreSyn/CoreOpt.hs12
-rw-r--r--compiler/nativeGen/RegAlloc/Graph/ArchBase.hs2
-rw-r--r--compiler/simplCore/CallArity.hs11
-rw-r--r--compiler/simplCore/Simplify.hs2
-rw-r--r--compiler/specialise/Specialise.hs2
-rw-r--r--compiler/typecheck/TcHsType.hs2
-rw-r--r--libraries/base/Data/Bifoldable.hs2
-rw-r--r--testsuite/tests/programs/joao-circular/Visfun_Lazy.hs6
9 files changed, 20 insertions, 21 deletions
diff --git a/compiler/basicTypes/NameEnv.hs b/compiler/basicTypes/NameEnv.hs
index 640084b403..a0eb933469 100644
--- a/compiler/basicTypes/NameEnv.hs
+++ b/compiler/basicTypes/NameEnv.hs
@@ -61,7 +61,7 @@ depAnal :: (node -> [Name]) -- Defs
-> (node -> [Name]) -- Uses
-> [node]
-> [SCC node]
--- Peform dependency analysis on a group of definitions,
+-- Perform dependency analysis on a group of definitions,
-- where each definition may define more than one Name
--
-- The get_defs and get_uses functions are called only once per node
diff --git a/compiler/coreSyn/CoreOpt.hs b/compiler/coreSyn/CoreOpt.hs
index 98a590bb3d..da58a4b500 100644
--- a/compiler/coreSyn/CoreOpt.hs
+++ b/compiler/coreSyn/CoreOpt.hs
@@ -143,7 +143,7 @@ simpleOptPgm dflags this_mod binds rules vects
rules' = substRulesForImportedIds final_subst rules
vects' = substVects final_subst vects
-- We never unconditionally inline into rules,
- -- hence pasing just a substitution
+ -- hence paying just a substitution
do_one (env, binds') bind
= case simple_opt_bind env bind of
@@ -686,9 +686,9 @@ Moreover, since g is going to be inlined anyway, there is no benefit
from making it a join point.
If it is recursive, and uselessly marked INLINE, this will stop us
-making it a join point, which is a annoying. But occasionally
+making it a join point, which is annoying. But occasionally
(notably in class methods; see Note [Instances and loop breakers] in
-TcInstDcls) we mark recurive things as INLINE but the recursion
+TcInstDcls) we mark recursive things as INLINE but the recursion
unravels; so ignoring INLINE pragmas on recursive things isn't good
either.
@@ -755,7 +755,7 @@ data ConCont = CC [CoreExpr] Coercion
-- | Returns @Just (dc, [t1..tk], [x1..xn])@ if the argument expression is
-- a *saturated* constructor application of the form @dc t1..tk x1 .. xn@,
--- where t1..tk are the *universally-qantified* type args of 'dc'
+-- where t1..tk are the *universally-quantified* type args of 'dc'
exprIsConApp_maybe :: InScopeEnv -> CoreExpr -> Maybe (DataCon, [Type], [CoreExpr])
exprIsConApp_maybe (in_scope, id_unf) expr
= go (Left in_scope) expr (CC [] (mkRepReflCo (exprType expr)))
@@ -961,7 +961,7 @@ Here we implement the "push rules" from FC papers:
(K e1 .. en) |> co
and we want to tranform to
(K e1' .. en')
- by pushing the coercion into the oarguments
+ by pushing the coercion into the arguments
-}
pushCoArgs :: Coercion -> [CoreArg] -> Maybe ([CoreArg], Coercion)
@@ -1081,7 +1081,7 @@ pushCoDataCon dc dc_args co
-- (C x y) `cast` (g :: T a ~ S [a]),
-- where S is a type function. In fact, exprIsConApp
-- will probably not be called in such circumstances,
- -- but there't nothing wrong with it
+ -- but there's nothing wrong with it
= let
tc_arity = tyConArity to_tc
diff --git a/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs b/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs
index 5731f18234..6771e4ecb9 100644
--- a/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs
+++ b/compiler/nativeGen/RegAlloc/Graph/ArchBase.hs
@@ -27,7 +27,7 @@ import Unique
-- Some basic register classes.
--- These aren't nessesarally in 1-to-1 correspondance with the allocatable
+-- These aren't necessarily in 1-to-1 correspondence with the allocatable
-- RegClasses in MachRegs.hs
data RegClass
-- general purpose regs
diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs
index c051dae456..1eb4fa22fd 100644
--- a/compiler/simplCore/CallArity.hs
+++ b/compiler/simplCore/CallArity.hs
@@ -16,7 +16,6 @@ import CoreSyn
import Id
import CoreArity ( typeArity )
import CoreUtils ( exprIsCheap, exprIsTrivial )
---import Outputable
import UnVarGraph
import Demand
@@ -26,7 +25,7 @@ import Control.Arrow ( first, second )
{-
%************************************************************************
%* *
- Call Arity Analyis
+ Call Arity Analysis
%* *
%************************************************************************
@@ -76,7 +75,7 @@ correct.
What we want to know from an expression
---------------------------------------
-In order to obtain that information for variables, we analyize expression and
+In order to obtain that information for variables, we analyze expression and
obtain bits of information:
I. The arity analysis:
@@ -95,7 +94,7 @@ For efficiency reasons, we gather this information only for a set of
The two analysis are not completely independent, as a higher arity can improve
the information about what variables are being called once or multiple times.
-Note [Analysis I: The arity analyis]
+Note [Analysis I: The arity analysis]
------------------------------------
The arity analysis is quite straight forward: The information about an
@@ -104,7 +103,7 @@ expression is an
where absent variables are bound to Nothing and otherwise to a lower bound to
their arity.
-When we analyize an expression, we analyize it with a given context arity.
+When we analyze an expression, we analyze it with a given context arity.
Lambdas decrease and applications increase the incoming arity. Analysizing a
variable will put that arity in the environment. In lets or cases all the
results from the various subexpressions are lubed, which takes the point-wise
@@ -687,7 +686,7 @@ trimArity v a = minimum [a, max_arity_by_type, max_arity_by_strsig]
---------------------------------------
-- Result type for the two analyses.
--- See Note [Analysis I: The arity analyis]
+-- See Note [Analysis I: The arity analysis]
-- and Note [Analysis II: The Co-Called analysis]
type CallArityRes = (UnVarGraph, VarEnv Arity)
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index 4b158b607a..fae040f47a 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -2238,7 +2238,7 @@ inlined.
Historical note: we use to do the "case binder swap" in the Simplifier
so there were additional complications if the scrutinee was a variable.
-Now the binder-swap stuff is done in the occurrence analyer; see
+Now the binder-swap stuff is done in the occurrence analyser; see
OccurAnal Note [Binder swap].
Note [knownCon occ info]
diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs
index 0dd295d695..37afca5e6f 100644
--- a/compiler/specialise/Specialise.hs
+++ b/compiler/specialise/Specialise.hs
@@ -1292,7 +1292,7 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs
herald = case mb_mod of
Nothing -- Specialising local fn
-> text "SPEC"
- Just this_mod -- Specialising imoprted fn
+ Just this_mod -- Specialising imported fn
-> text "SPEC/" <> ppr this_mod
rule_name = mkFastString $ showSDoc dflags $
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index e5dcd7ccc6..99fc6dd901 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -1081,7 +1081,7 @@ Note [Body kind of a HsForAllTy]
The body of a forall is usually a type, but in principle
there's no reason to prohibit *unlifted* types.
In fact, GHC can itself construct a function with an
-unboxed tuple inside a for-all (via CPR analyis; see
+unboxed tuple inside a for-all (via CPR analysis; see
typecheck/should_compile/tc170).
Moreover in instance heads we get forall-types with
diff --git a/libraries/base/Data/Bifoldable.hs b/libraries/base/Data/Bifoldable.hs
index 9006e61fdd..1f632e2ff9 100644
--- a/libraries/base/Data/Bifoldable.hs
+++ b/libraries/base/Data/Bifoldable.hs
@@ -117,7 +117,7 @@ class Bifoldable p where
bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> p a b -> c
bifoldr f g z t = appEndo (bifoldMap (Endo #. f) (Endo #. g) t) z
- -- | Combines the elments of a structure in a left associative manner. Given
+ -- | Combines the elements of a structure in a left associative manner. Given
-- a hypothetical function @toEitherList :: p a b -> [Either a b]@ yielding a
-- list of all elements of a structure in order, the following would hold:
--
diff --git a/testsuite/tests/programs/joao-circular/Visfun_Lazy.hs b/testsuite/tests/programs/joao-circular/Visfun_Lazy.hs
index 6430e549ab..e4055350a1 100644
--- a/testsuite/tests/programs/joao-circular/Visfun_Lazy.hs
+++ b/testsuite/tests/programs/joao-circular/Visfun_Lazy.hs
@@ -926,7 +926,7 @@ afmt_txt string =
allf fs =
case fs of { ( [] ) -> "" ; ( (:) f fs2 ) -> ((txtstr f 0 "\n\n")++(best fs2)) }
assign_InfType n exptype fid env =
- let { (desttype) = (gettype n fid env) } in (if ((coersibleTypes desttype exptype)==(C_Errortype_1 )) then (C_E_T_NC_1 desttype exptype) else (C_NoTypeError_1 ))
+ let { (desttype) = (gettype n fid env) } in (if ((coercibleTypes desttype exptype)==(C_Errortype_1 )) then (C_E_T_NC_1 desttype exptype) else (C_NoTypeError_1 ))
asts i =
(if (i==0) then "" else (if (i==1) then "*" else ((":"++(repeatCHAR '*' (fromIntegral (i-2))))++"*>")) )
beside_fmt l r =
@@ -945,7 +945,7 @@ choose_ab_beside_fmts avail fa fb f =
(if avail then (beside_fmts f fa fb) else (above_fmts fa fb))
choose_ab_error_beside avail fa fb f =
(if avail then (error_beside fa fb) else (above_fmts fa fb))
-coersibleTypes t1 t2 =
+coercibleTypes t1 t2 =
(if (t1==t2) then t1 else case t1 of { (C_Realtype_1 ) -> case t2 of { (C_Inttype_1 ) -> t1 ; _ -> (C_Errortype_1 ) } ; _ -> (C_Errortype_1 ) } )
cons_height pph acth avail =
(if (acth==0) then (if (pph>0) then 1 else 0) else (acth+(if avail then 0 else 1) ))
@@ -1034,7 +1034,7 @@ indent_fmt i f =
indent_fmts f i fs =
case f of { (C_F_1 pw _) -> (map_indent_fmt i (dropWhileFormatsNotFit (pw-i) fs)) }
infType op t1 t2 =
- case op of { 1 -> (coersibleTypes t1 t2) ; 2 -> (if (t1==t2) then (C_Booltype_1 ) else (C_Errortype_1 )) ; _ -> (C_Errortype_1 ) }
+ case op of { 1 -> (coercibleTypes t1 t2) ; 2 -> (if (t1==t2) then (C_Booltype_1 ) else (C_Errortype_1 )) ; _ -> (C_Errortype_1 ) }
initLst_Str l =
case l of { ( [] ) -> ([] ) ; ( (:) x ( [] ) ) -> ([] ) ; ( (:) x ls ) -> ((:) x (initLst_Str ls)) }
isaritmexp t =