summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorBrian Wignall <brianwignall@gmail.com>2019-11-08 16:21:03 -0500
committerBrian Wignall <brianwignall@gmail.com>2019-11-23 19:04:52 -0500
commit7b4c7b75be351e9b6a40093cbccab728dd89064f (patch)
tree01126ac3823a1f1b197ac1865d7bc628eb4676a5 /compiler
parentc14b723f7fa24b4db0b561f9ab0d6e0f4261fd2f (diff)
downloadhaskell-7b4c7b75be351e9b6a40093cbccab728dd89064f.tar.gz
Fix typos
Diffstat (limited to 'compiler')
-rw-r--r--compiler/basicTypes/Id.hs2
-rw-r--r--compiler/basicTypes/VarSet.hs4
-rw-r--r--compiler/cmm/CmmSwitch.hs2
-rw-r--r--compiler/coreSyn/CoreFVs.hs2
-rw-r--r--compiler/iface/IfaceEnv.hs2
-rw-r--r--compiler/main/SysTools/Tasks.hs2
-rw-r--r--compiler/nativeGen/BlockLayout.hs3
-rw-r--r--compiler/prelude/PrelRules.hs6
-rw-r--r--compiler/rename/RnNames.hs2
-rw-r--r--compiler/simplCore/SetLevels.hs2
-rw-r--r--compiler/simplCore/SimplUtils.hs2
-rw-r--r--compiler/simplStg/StgLiftLams/Analysis.hs2
-rw-r--r--compiler/specialise/Specialise.hs4
-rw-r--r--compiler/typecheck/TcBinds.hs2
-rw-r--r--compiler/typecheck/TcClassDcl.hs2
-rw-r--r--compiler/typecheck/TcDeriv.hs2
-rw-r--r--compiler/typecheck/TcEnv.hs4
-rw-r--r--compiler/typecheck/TcFlatten.hs4
-rw-r--r--compiler/typecheck/TcPat.hs2
-rw-r--r--compiler/typecheck/TcUnify.hs2
-rw-r--r--compiler/types/Unify.hs2
-rw-r--r--compiler/utils/Binary.hs2
22 files changed, 28 insertions, 29 deletions
diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs
index 8c62cc9944..9504175cca 100644
--- a/compiler/basicTypes/Id.hs
+++ b/compiler/basicTypes/Id.hs
@@ -559,7 +559,7 @@ idIsFrom mod id = nameIsLocalOrFrom mod (idName id)
{- Note [Levity-polymorphic Ids]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Some levity-polymorphic Ids must be applied and and inlined, not left
+Some levity-polymorphic Ids must be applied and inlined, not left
un-saturated. Example:
unsafeCoerceId :: forall r1 r2 (a::TYPE r1) (b::TYPE r2). a -> b
diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs
index ec8a325b25..2cf15eb3e5 100644
--- a/compiler/basicTypes/VarSet.hs
+++ b/compiler/basicTypes/VarSet.hs
@@ -171,7 +171,7 @@ transCloVarSet :: (VarSet -> VarSet)
-- The function fn could be (Var -> VarSet), but we use (VarSet -> VarSet)
-- for efficiency, so that the test can be batched up.
-- It's essential that fn will work fine if given new candidates
--- one at at time; ie fn {v1,v2} = fn v1 `union` fn v2
+-- one at a time; ie fn {v1,v2} = fn v1 `union` fn v2
-- Use fixVarSet if the function needs to see the whole set all at once
transCloVarSet fn seeds
= go seeds seeds
@@ -334,7 +334,7 @@ transCloDVarSet :: (DVarSet -> DVarSet)
-- The function fn could be (Var -> DVarSet), but we use (DVarSet -> DVarSet)
-- for efficiency, so that the test can be batched up.
-- It's essential that fn will work fine if given new candidates
--- one at at time; ie fn {v1,v2} = fn v1 `union` fn v2
+-- one at a time; ie fn {v1,v2} = fn v1 `union` fn v2
transCloDVarSet fn seeds
= go seeds seeds
where
diff --git a/compiler/cmm/CmmSwitch.hs b/compiler/cmm/CmmSwitch.hs
index c2ce3b9e00..a5fa6457e2 100644
--- a/compiler/cmm/CmmSwitch.hs
+++ b/compiler/cmm/CmmSwitch.hs
@@ -195,7 +195,7 @@ switchTargetsToTable (SwitchTargets _ (lo,hi) mbdef branches)
-- .quad _c20q
-- .quad _c20r
--- | The list of all labels occuring in the SwitchTargets value.
+-- | The list of all labels occurring in the SwitchTargets value.
switchTargetsToList :: SwitchTargets -> [Label]
switchTargetsToList (SwitchTargets _ _ mbdef branches)
= maybeToList mbdef ++ M.elems branches
diff --git a/compiler/coreSyn/CoreFVs.hs b/compiler/coreSyn/CoreFVs.hs
index 7f52054496..fef3915c51 100644
--- a/compiler/coreSyn/CoreFVs.hs
+++ b/compiler/coreSyn/CoreFVs.hs
@@ -210,7 +210,7 @@ exprsSomeFreeVarsDSet :: InterestingVarFun -- ^ Says which 'Var's are interestin
exprsSomeFreeVarsDSet fv_cand e =
fvDVarSet $ filterFV fv_cand $ mapUnionFV expr_fvs e
--- Comment about obselete code
+-- Comment about obsolete code
-- We used to gather the free variables the RULES at a variable occurrence
-- with the following cryptic comment:
-- "At a variable occurrence, add in any free variables of its rule rhss
diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs
index 864c09ce2e..2bcfa82c96 100644
--- a/compiler/iface/IfaceEnv.hs
+++ b/compiler/iface/IfaceEnv.hs
@@ -87,7 +87,7 @@ allocateGlobalBinder name_supply mod occ loc
-- of the Name, so we set this field in the Name we return.
--
-- Then (bogus) multiple bindings of the same Name
- -- get different SrcLocs can can be reported as such.
+ -- get different SrcLocs can be reported as such.
--
-- Possible other reason: it might be in the cache because we
-- encountered an occurrence before the binding site for an
diff --git a/compiler/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs
index 96a5b291da..ee6824327a 100644
--- a/compiler/main/SysTools/Tasks.hs
+++ b/compiler/main/SysTools/Tasks.hs
@@ -242,7 +242,7 @@ runLink dflags args = traceToolCommand dflags "linker" $ do
--
-- `-optl` args come at the end, so that later `-l` options
-- given there manually can fill in symbols needed by
- -- Haskell libaries coming in via `args`.
+ -- Haskell libraries coming in via `args`.
linkargs <- neededLinkArgs `fmap` getLinkerInfo dflags
let (p,args0) = pgm_l dflags
optl_args = map Option (getOpts dflags opt_l)
diff --git a/compiler/nativeGen/BlockLayout.hs b/compiler/nativeGen/BlockLayout.hs
index 56e3177dd8..d8b844c32b 100644
--- a/compiler/nativeGen/BlockLayout.hs
+++ b/compiler/nativeGen/BlockLayout.hs
@@ -359,7 +359,7 @@ takeL n (BlockChain blks) =
-- While we could take into account the space between the two blocks which
-- share an edge this blows up compile times quite a bit. It requires
-- us to find all edges between two chains, check the distance for all edges,
--- rank them based on the distance and and only then we can select two chains
+-- rank them based on the distance and only then we can select two chains
-- to combine. Which would add a lot of complexity for little gain.
--
-- So instead we just rank by the strength of the edge and use the first pair we
@@ -891,4 +891,3 @@ lookupDeleteUFM :: Uniquable key => UniqFM elt -> key
lookupDeleteUFM m k = do -- Maybe monad
v <- lookupUFM m k
return (v, delFromUFM m k)
-
diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs
index ffee79da36..a61c163c32 100644
--- a/compiler/prelude/PrelRules.hs
+++ b/compiler/prelude/PrelRules.hs
@@ -855,7 +855,7 @@ leftIdentityDynFlags id_lit = do
return e2
-- | Left identity rule for PrimOps like 'IntAddC' and 'WordAddC', where, in
--- addition to the result, we have to indicate that no carry/overflow occured.
+-- addition to the result, we have to indicate that no carry/overflow occurred.
leftIdentityCDynFlags :: (DynFlags -> Literal) -> RuleM CoreExpr
leftIdentityCDynFlags id_lit = do
dflags <- getDynFlags
@@ -872,7 +872,7 @@ rightIdentityDynFlags id_lit = do
return e1
-- | Right identity rule for PrimOps like 'IntSubC' and 'WordSubC', where, in
--- addition to the result, we have to indicate that no carry/overflow occured.
+-- addition to the result, we have to indicate that no carry/overflow occurred.
rightIdentityCDynFlags :: (DynFlags -> Literal) -> RuleM CoreExpr
rightIdentityCDynFlags id_lit = do
dflags <- getDynFlags
@@ -886,7 +886,7 @@ identityDynFlags lit =
leftIdentityDynFlags lit `mplus` rightIdentityDynFlags lit
-- | Identity rule for PrimOps like 'IntAddC' and 'WordAddC', where, in addition
--- to the result, we have to indicate that no carry/overflow occured.
+-- to the result, we have to indicate that no carry/overflow occurred.
identityCDynFlags :: (DynFlags -> Literal) -> RuleM CoreExpr
identityCDynFlags lit =
leftIdentityCDynFlags lit `mplus` rightIdentityCDynFlags lit
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 8d1083a547..7614fb1932 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -92,7 +92,7 @@ mode changes, this triggers a recompilation from that module in the dependcy
graph. So we can just worry mostly about direct imports.
There is one trust property that can change for a package though without
-recompliation being triggered: package trust. So we must check that all
+recompilation being triggered: package trust. So we must check that all
packages a module tranitively depends on to be trusted are still trusted when
we are compiling this module (as due to recompilation avoidance some modules
below may not be considered trusted any more without recompilation being
diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs
index da1e31ea6f..223bbcfa97 100644
--- a/compiler/simplCore/SetLevels.hs
+++ b/compiler/simplCore/SetLevels.hs
@@ -777,7 +777,7 @@ Exammples:
It's controlled by a flag (floatConsts), because doing this too
early loses opportunities for RULES which (needless to say) are
important in some nofib programs (gcd is an example). [SPJ note:
-I think this is obselete; the flag seems always on.]
+I think this is obsolete; the flag seems always on.]
Note [Floating join point bindings]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs
index 5073bbff99..e8829c845c 100644
--- a/compiler/simplCore/SimplUtils.hs
+++ b/compiler/simplCore/SimplUtils.hs
@@ -558,7 +558,7 @@ discarding the arguments to zip. Usually this is fine, but on the
LHS of a rule it's not, because 'as' and 'bs' are now not bound on
the LHS.
-This is a pretty pathalogical example, so I'm not losing sleep over
+This is a pretty pathological example, so I'm not losing sleep over
it, but the simplest solution was to check sm_inline; if it is False,
which it is on the LHS of a rule (see updModeForRules), then don't
make use of the strictness info for the function.
diff --git a/compiler/simplStg/StgLiftLams/Analysis.hs b/compiler/simplStg/StgLiftLams/Analysis.hs
index 104c2f8ef3..8bcd6f6cb5 100644
--- a/compiler/simplStg/StgLiftLams/Analysis.hs
+++ b/compiler/simplStg/StgLiftLams/Analysis.hs
@@ -412,7 +412,7 @@ goodToLift dflags top_lvl rec_flag expander pairs scope = decide
is_memoized_rhs StgRhsCon{} = True
is_memoized_rhs (StgRhsClosure _ _ upd _ _) = isUpdatable upd
- -- Don't lift binders occuring as arguments. This would result in complex
+ -- Don't lift binders occurring as arguments. This would result in complex
-- argument expressions which would have to be given a name, reintroducing
-- the very allocation at each call site that we wanted to get rid off in
-- the first place.
diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs
index 75e80d0c46..96c29f4f21 100644
--- a/compiler/specialise/Specialise.hs
+++ b/compiler/specialise/Specialise.hs
@@ -576,7 +576,7 @@ Hence, the invariant is this:
************************************************************************
-}
--- | Specialise calls to type-class overloaded functions occuring in a program.
+-- | Specialise calls to type-class overloaded functions occurring in a program.
specProgram :: ModGuts -> CoreM ModGuts
specProgram guts@(ModGuts { mg_module = this_mod
, mg_rules = local_rules
@@ -2107,7 +2107,7 @@ Consider
We gather the call info for (f @T $df), and we don't want to drop it
when we come across the binding for $df. So we add $df to the floats
and continue. But then we have to add $c== to the floats, and so on.
-These all float above the binding for 'f', and and now we can
+These all float above the binding for 'f', and now we can
successfully specialise 'f'.
So the DictBinds in (ud_binds :: Bag DictBind) may contain
diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs
index 6421be4f16..b51b0041e3 100644
--- a/compiler/typecheck/TcBinds.hs
+++ b/compiler/typecheck/TcBinds.hs
@@ -342,7 +342,7 @@ tcLocalBinds (HsIPBinds x (IPBinds _ ip_binds)) thing_inside
where
ips = [ip | (dL->L _ (IPBind _ (Left (dL->L _ ip)) _)) <- ip_binds]
- -- I wonder if we should do these one at at time
+ -- I wonder if we should do these one at a time
-- Consider ?x = 4
-- ?y = ?x + 1
tc_ip_bind ipClass (IPBind _ (Left (dL->L _ ip)) expr)
diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs
index 18e71c8803..09a9bb2f6e 100644
--- a/compiler/typecheck/TcClassDcl.hs
+++ b/compiler/typecheck/TcClassDcl.hs
@@ -78,7 +78,7 @@ would implicitly declare
(forall b. Ord b => a -> b -> b)
(We could use a record decl, but that means changing more of the existing apparatus.
-One step at at time!)
+One step at a time!)
For classes with just one superclass+method, we use a newtype decl instead:
diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs
index a6c44d0c45..3a7369e2f9 100644
--- a/compiler/typecheck/TcDeriv.hs
+++ b/compiler/typecheck/TcDeriv.hs
@@ -369,7 +369,7 @@ the rest of the instance. The fact that it is suspended is important, because
right now, we don't have ThetaTypes for the instances that use deriving clauses
(only the standalone-derived ones).
-Now we can can collect the type family instances and extend the local instance
+Now we can collect the type family instances and extend the local instance
environment. At this point, it is safe to run simplifyInstanceContexts on the
deriving-clause instance specs, which gives us the ThetaTypes for the
deriving-clause instances. Now we can feed all the ThetaTypes to the
diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs
index d9bd893dc5..725274bbaf 100644
--- a/compiler/typecheck/TcEnv.hs
+++ b/compiler/typecheck/TcEnv.hs
@@ -509,7 +509,7 @@ isTypeClosedLetBndr = noFreeVarsOfType . idType
tcExtendRecIds :: [(Name, TcId)] -> TcM a -> TcM a
-- Used for binding the recurive uses of Ids in a binding
--- both top-level value bindings and and nested let/where-bindings
+-- both top-level value bindings and nested let/where-bindings
-- Does not extend the TcBinderStack
tcExtendRecIds pairs thing_inside
= tc_extend_local_env NotTopLevel
@@ -533,7 +533,7 @@ tcExtendSigIds top_lvl sig_ids thing_inside
tcExtendLetEnv :: TopLevelFlag -> TcSigFun -> IsGroupClosed
-> [TcId] -> TcM a -> TcM a
--- Used for both top-level value bindings and and nested let/where-bindings
+-- Used for both top-level value bindings and nested let/where-bindings
-- Adds to the TcBinderStack too
tcExtendLetEnv top_lvl sig_fn (IsGroupClosed fvs fv_type_closed)
ids thing_inside
diff --git a/compiler/typecheck/TcFlatten.hs b/compiler/typecheck/TcFlatten.hs
index fed20bf810..5d5589df9a 100644
--- a/compiler/typecheck/TcFlatten.hs
+++ b/compiler/typecheck/TcFlatten.hs
@@ -714,7 +714,7 @@ other examples where lazy flattening caused problems.
Bottom line: FM_Avoid is unused for now (Nov 14).
Note: T5321Fun got faster when I disabled FM_Avoid
- T5837 did too, but it's pathalogical anyway
+ T5837 did too, but it's pathological anyway
Note [Phantoms in the flattener]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1708,7 +1708,7 @@ is an example; all the constraints here are Givens
inert fsk ~ ((fsk3, TF Int), TF Int)
Because the incoming given rewrites all the inert givens, we get more and
-more duplication in the inert set. But this really only happens in pathalogical
+more duplication in the inert set. But this really only happens in pathological
casee, so we don't care.
diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs
index 6d68cd5904..d18b2af252 100644
--- a/compiler/typecheck/TcPat.hs
+++ b/compiler/typecheck/TcPat.hs
@@ -1101,7 +1101,7 @@ So for now I'm just insisting on type *equality* in patterns. No subsumption.
Old notes about desugaring, at a time when pattern coercions were handled:
-A SigPat is a type coercion and must be handled one at at time. We can't
+A SigPat is a type coercion and must be handled one at a time. We can't
combine them unless the type of the pattern inside is identical, and we don't
bother to check for that. For example:
diff --git a/compiler/typecheck/TcUnify.hs b/compiler/typecheck/TcUnify.hs
index 44842e43ae..9f9e69850d 100644
--- a/compiler/typecheck/TcUnify.hs
+++ b/compiler/typecheck/TcUnify.hs
@@ -1715,7 +1715,7 @@ uUnfilledVar2 origin t_or_k swapped tv1 ty2
= do { traceTc "uUnfilledVar2 not ok" (ppr tv1 $$ ppr ty2)
-- Occurs check or an untouchable: just defer
-- NB: occurs check isn't necessarily fatal:
- -- eg tv1 occured in type family parameter
+ -- eg tv1 occurred in type family parameter
; defer }
ty1 = mkTyVarTy tv1
diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs
index 63f024a824..0e41ca66ac 100644
--- a/compiler/types/Unify.hs
+++ b/compiler/types/Unify.hs
@@ -922,7 +922,7 @@ we invoke
Although we have unified k and j, it's very important that we put
(Refl j), /not/ (Refl k) as the fourth argument to unify_tys.
-If we put (Refl k) we'd end up with teh substitution
+If we put (Refl k) we'd end up with the substitution
a :-> b |> Refl k
which is bogus because one of the template variables, k,
appears in the range of the substitution. Eek.
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index 503dd31690..b1337a1e14 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -449,7 +449,7 @@ putSLEB128 bh initial = go initial
let !val' = val `unsafeShiftR` 7
let !signBit = testBit byte 6
let !done =
- -- Unsigned value, val' == 0 and and last value can
+ -- Unsigned value, val' == 0 and last value can
-- be discriminated from a negative number.
((val' == 0 && not signBit) ||
-- Signed value,