diff options
-rw-r--r-- | compiler/basicTypes/Demand.hs | 2 | ||||
-rw-r--r-- | compiler/ghci/ByteCodeGen.hs | 2 | ||||
-rw-r--r-- | compiler/nativeGen/RegAlloc/Graph/Stats.hs | 4 | ||||
-rw-r--r-- | compiler/simplCore/SimplEnv.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/FunDeps.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcBinds.hs | 12 | ||||
-rw-r--r-- | compiler/typecheck/TcPat.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcRules.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcSigs.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcTypeable.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcValidity.hs | 2 | ||||
-rw-r--r-- | compiler/types/TyCoRep.hs | 2 | ||||
-rw-r--r-- | compiler/utils/GraphColor.hs | 2 | ||||
-rw-r--r-- | compiler/utils/GraphOps.hs | 2 | ||||
-rw-r--r-- | docs/rts/rts.tex | 2 | ||||
-rw-r--r-- | libraries/base/GHC/Base.hs | 4 | ||||
-rw-r--r-- | libraries/ghc-compact/GHC/Compact.hs | 2 | ||||
-rw-r--r-- | testsuite/tests/profiling/should_run/heapprof001.hs | 2 | ||||
-rw-r--r-- | testsuite/tests/safeHaskell/overlapping/SH_Overlap3.hs | 2 |
19 files changed, 26 insertions, 26 deletions
diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index e3984d7efb..377fc3d6ea 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1229,7 +1229,7 @@ diverge, and we do not anything being passed to b. Note [Asymmetry of 'both' for DmdType and DmdResult] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -'both' for DmdTypes is *assymetrical*, because there is only one +'both' for DmdTypes is *asymmetrical*, because there is only one result! For example, given (e1 e2), we get a DmdType dt1 for e1, use its arg demand to analyse e2 giving dt2, and then do (dt1 `bothType` dt2). Similarly with diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index 854eee28da..5484288a9b 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -180,7 +180,7 @@ coreExprToBCOs hsc_env this_mod expr where dflags = hsc_dflags hsc_env -- The regular freeVars function gives more information than is useful to --- us here. simpleFreeVars does the impedence matching. +-- us here. simpleFreeVars does the impedance matching. simpleFreeVars :: CoreExpr -> AnnExpr Id DVarSet simpleFreeVars = go . freeVars where diff --git a/compiler/nativeGen/RegAlloc/Graph/Stats.hs b/compiler/nativeGen/RegAlloc/Graph/Stats.hs index 9a8d0068ff..71956025b0 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Stats.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Stats.hs @@ -60,7 +60,7 @@ data RegAllocStats statics instr -- | Partially colored graph. , raGraph :: Color.Graph VirtualReg RegClass RealReg - -- | The regs that were coaleced. + -- | The regs that were coalesced. , raCoalesced :: UniqFM VirtualReg -- | Spiller stats. @@ -84,7 +84,7 @@ data RegAllocStats statics instr -- | Coalesced and colored graph. , raGraphColored :: Color.Graph VirtualReg RegClass RealReg - -- | Regs that were coaleced. + -- | Regs that were coalesced. , raCoalesced :: UniqFM VirtualReg -- | Code with coalescings applied. diff --git a/compiler/simplCore/SimplEnv.hs b/compiler/simplCore/SimplEnv.hs index c244ae40c6..137964661b 100644 --- a/compiler/simplCore/SimplEnv.hs +++ b/compiler/simplCore/SimplEnv.hs @@ -790,7 +790,7 @@ the letrec. {- ************************************************************************ * * - Impedence matching to type substitution + Impedance matching to type substitution * * ************************************************************************ -} diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index 981702fc9b..fff8979e0d 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -212,7 +212,7 @@ improveFromInstEnv inst_env mk_loc pred -- because there often are none! , let trimmed_tcs = trimRoughMatchTcs cls_tvs fd rough_tcs -- Trim the rough_tcs based on the head of the fundep. - -- Remember that instanceCantMatch treats both argumnents + -- Remember that instanceCantMatch treats both arguments -- symmetrically, so it's ok to trim the rough_tcs, -- rather than trimming each inst_tcs in turn , ispec <- instances diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index 942bf96988..eef20a29bf 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -831,7 +831,7 @@ mkExport prag_fn qtvs theta ; spec_prags <- tcSpecPrags poly_id prag_sigs -- tcPrags requires a zonked poly_id - -- See Note [Impedence matching] + -- See Note [Impedance matching] -- NB: we have already done checkValidType, including an ambiguity check, -- on the type; either when we checked the sig or in mkInferredPolyId ; let poly_ty = idType poly_id @@ -843,7 +843,7 @@ mkExport prag_fn qtvs theta then return idHsWrapper -- Fast path; also avoids complaint when we infer -- an ambiguouse type and have AllowAmbiguousType -- e..g infer x :: forall a. F a -> Int - else addErrCtxtM (mk_impedence_match_msg mono_info sel_poly_ty poly_ty) $ + else addErrCtxtM (mk_impedance_match_msg mono_info sel_poly_ty poly_ty) $ tcSubType_NC sig_ctxt sel_poly_ty poly_ty ; warn_missing_sigs <- woptM Opt_WarnMissingLocalSignatures @@ -869,7 +869,7 @@ mkInferredPolyId qtvs inferred_theta poly_name mb_sig_inst mono_ty | otherwise -- Either no type sig or partial type sig = checkNoErrs $ -- The checkNoErrs ensures that if the type is ambiguous - -- we don't carry on to the impedence matching, and generate + -- we don't carry on to the impedance matching, and generate -- a duplicate ambiguity error. There is a similar -- checkNoErrs for complete type signatures too. do { fam_envs <- tcGetFamInstEnvs @@ -966,11 +966,11 @@ chooseInferredQuantifiers inferred_theta tau_tvs qtvs mk_ctuple preds = do { tc <- tcLookupTyCon (cTupleTyConName (length preds)) ; return (mkTyConApp tc preds) } -mk_impedence_match_msg :: MonoBindInfo +mk_impedance_match_msg :: MonoBindInfo -> TcType -> TcType -> TidyEnv -> TcM (TidyEnv, SDoc) -- This is a rare but rather awkward error messages -mk_impedence_match_msg (MBI { mbi_poly_name = name, mbi_sig = mb_sig }) +mk_impedance_match_msg (MBI { mbi_poly_name = name, mbi_sig = mb_sig }) inf_ty sig_ty tidy_env = do { (tidy_env1, inf_ty) <- zonkTidyTcType tidy_env inf_ty ; (tidy_env2, sig_ty) <- zonkTidyTcType tidy_env1 sig_ty @@ -1077,7 +1077,7 @@ Examples that might fail: - an inferred type that includes unboxed tuples -Note [Impedence matching] +Note [Impedance matching] ~~~~~~~~~~~~~~~~~~~~~~~~~ Consider f 0 x = x diff --git a/compiler/typecheck/TcPat.hs b/compiler/typecheck/TcPat.hs index ebf10cbb22..486210cb07 100644 --- a/compiler/typecheck/TcPat.hs +++ b/compiler/typecheck/TcPat.hs @@ -243,7 +243,7 @@ subsumption, not equality, check against the context type. e.g. Since 'blah' returns a value of type T, its payload is a polymorphic function of type (forall a. a->a). And that's enough to bind the -less-polymorphic function 'f', but we need some impedence matching +less-polymorphic function 'f', but we need some impedance matching to witness the instantiation. diff --git a/compiler/typecheck/TcRules.hs b/compiler/typecheck/TcRules.hs index 3c7b8055b1..dd773cf041 100644 --- a/compiler/typecheck/TcRules.hs +++ b/compiler/typecheck/TcRules.hs @@ -285,7 +285,7 @@ These don't have a name, so we can't quantify over them directly. Instead, because we really do want to quantify here, invent a new EvVar for the coercion, fill the hole with the invented EvVar, and then quantify over the EvVar. Not too tricky -- just some -impedence matching, really. +impedance matching, really. Note [Simplify cloned constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcSigs.hs b/compiler/typecheck/TcSigs.hs index e26133ed3d..989fe94e8c 100644 --- a/compiler/typecheck/TcSigs.hs +++ b/compiler/typecheck/TcSigs.hs @@ -470,7 +470,7 @@ the signature types for f and g, we'll end up unifying 'a' and 'b' So we instantiate f and g's signature with SigTv skolems (newMetaSigTyVars) that can unify with each other. If too much unification takes place, we'll find out when we do the final -impedence-matching check in TcBinds.mkExport +impedance-matching check in TcBinds.mkExport See Note [Signature skolems] in TcType diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 8dfad6d3df..34bd387a8d 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -450,7 +450,7 @@ typeIsTypeable (CoercionTy{}) = panic "typeIsTypeable(Coercion)" type KindRepEnv = TypeMap (Id, Maybe (LHsExpr Id)) -- | A monad within which we will generate 'KindRep's. Here we keep an --- environments containing 'KindRep's which we've already generated so we can +-- environment containing 'KindRep's which we've already generated so we can -- re-use them opportunistically. newtype KindRepM a = KindRepM { unKindRepM :: StateT KindRepEnv TcRn a } deriving (Functor, Applicative, Monad) diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 725f9dcd48..0dd5af3f95 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -118,7 +118,7 @@ and fail. So in fact we use this as our *definition* of ambiguity. We use a very similar test for *inferred* types, to ensure that they are -unambiguous. See Note [Impedence matching] in TcBinds. +unambiguous. See Note [Impedance matching] in TcBinds. This test is very conveniently implemented by calling tcSubType <type> <type> diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 494d66ab0d..8f9b1a5b45 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -954,7 +954,7 @@ mentions the same name with different kinds, but it *is* well-kinded, noting that `(tv1:k2) |> sym kind_co` has kind k1. This all really would work storing just a Name in the ForAllCo. But we can't -add Names to, e.g., VarSets, and there generally is just an impedence mismatch +add Names to, e.g., VarSets, and there generally is just an impedance mismatch in a bunch of places. So we use tv1. When we need tv2, we can use setTyVarKind. diff --git a/compiler/utils/GraphColor.hs b/compiler/utils/GraphColor.hs index 492125b787..be7975b306 100644 --- a/compiler/utils/GraphColor.hs +++ b/compiler/utils/GraphColor.hs @@ -45,7 +45,7 @@ colorGraph -> ( Graph k cls color -- the colored graph. , UniqSet k -- the set of nodes that we couldn't find a color for. - , UniqFM k ) -- map of regs (r1 -> r2) that were coaleced + , UniqFM k ) -- map of regs (r1 -> r2) that were coalesced -- r1 should be replaced by r2 in the source colorGraph iterative spinCount colors triv spill graph0 diff --git a/compiler/utils/GraphOps.hs b/compiler/utils/GraphOps.hs index 3677e517b5..565134be92 100644 --- a/compiler/utils/GraphOps.hs +++ b/compiler/utils/GraphOps.hs @@ -279,7 +279,7 @@ addPreference (u, c) color -- | Do aggressive coalescing on this graph. --- returns the new graph and the list of pairs of nodes that got coaleced together. +-- returns the new graph and the list of pairs of nodes that got coalesced together. -- for each pair, the resulting node will have the least key and be second in the pair. -- coalesceGraph diff --git a/docs/rts/rts.tex b/docs/rts/rts.tex index 191d65da9c..4337bb1f8e 100644 --- a/docs/rts/rts.tex +++ b/docs/rts/rts.tex @@ -309,7 +309,7 @@ Functions can take multiple arguments as easily as they can take one argument: there's no cost for adding another argument. But functions can only return one result: the cost of adding a second ``result'' is that the function must construct a tuple of ``results'' on the heap. -The assymetry is rather galling and can make certain programming +The asymmetry is rather galling and can make certain programming styles quite expensive. For example, consider a simple state transformer monad: \begin{verbatim} diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 3c3dbd3c7b..ffcd7ff2a0 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -974,14 +974,14 @@ The rules for map work like this. * The "mapFB" rule optimises compositions of map -* The "mapFB/id" rule get rids of 'map id' calls. +* The "mapFB/id" rule gets rid of 'map id' calls. You might think that (mapFB c id) will turn into c simply when mapFB is inlined; but before that happens the "mapList" rule turns (foldr (mapFB (:) id) [] a back into map id - Which is not very cleveer. + Which is not very clever. * Any similarity to the Functor laws for [] is expected. -} diff --git a/libraries/ghc-compact/GHC/Compact.hs b/libraries/ghc-compact/GHC/Compact.hs index d9581a521e..0464bc61f9 100644 --- a/libraries/ghc-compact/GHC/Compact.hs +++ b/libraries/ghc-compact/GHC/Compact.hs @@ -103,7 +103,7 @@ import GHC.Types -- separate copy of the data. -- -- The cost of compaction is similar to the cost of GC for the same --- data, but it is perfomed only once. However, because +-- data, but it is performed only once. However, because -- "Data.Compact.compact" does not stop-the-world, retaining internal -- sharing during the compaction process is very costly. The user -- can choose whether to 'compact' or 'compactWithSharing'. diff --git a/testsuite/tests/profiling/should_run/heapprof001.hs b/testsuite/tests/profiling/should_run/heapprof001.hs index 2e5bf192e1..c945631d33 100644 --- a/testsuite/tests/profiling/should_run/heapprof001.hs +++ b/testsuite/tests/profiling/should_run/heapprof001.hs @@ -169,7 +169,7 @@ split p = split' p [] spri (Ast x : Lex c : s) = opri c spri s = 0 --- does any symbol appear in both consequent and antecedant of clause +-- does any symbol appear in both consequent and antecedent of clause tautclause (c,a) = [x | x <- c, x `elem` a] /= [] -- form unique clausal axioms excluding tautologies diff --git a/testsuite/tests/safeHaskell/overlapping/SH_Overlap3.hs b/testsuite/tests/safeHaskell/overlapping/SH_Overlap3.hs index bbd5350b2d..8ffa53f84b 100644 --- a/testsuite/tests/safeHaskell/overlapping/SH_Overlap3.hs +++ b/testsuite/tests/safeHaskell/overlapping/SH_Overlap3.hs @@ -2,7 +2,7 @@ {-# LANGUAGE FlexibleInstances #-} -- | Same as SH_Overlap1, but module where overlap occurs (SH_Overlap3) is --- marked `Unsafe`. Compilation should succeed (symetry with inferring safety). +-- marked `Unsafe`. Compilation should succeed (symmetry with inferring safety). module SH_Overlap3 where import SH_Overlap3_A |