diff options
author | Gabor Greif <ggreif@gmail.com> | 2017-02-08 14:14:36 +0100 |
---|---|---|
committer | Gabor Greif <ggreif@gmail.com> | 2017-02-09 13:14:17 +0100 |
commit | e8f5efb55b694f70542d22d5c3aaf92222ccd973 (patch) | |
tree | 57f265e9826ce6ff8542ce4ebd8c73c630dbf0e2 /compiler | |
parent | b9bebd8cedccd7e8dd6df89b5504cd8f1e7a675b (diff) | |
download | haskell-e8f5efb55b694f70542d22d5c3aaf92222ccd973.tar.gz |
Tweaks and typos in manual, note refs, comments
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/basicTypes/Demand.hs | 2 | ||||
-rw-r--r-- | compiler/cmm/CmmSink.hs | 2 | ||||
-rw-r--r-- | compiler/codeGen/StgCmmCon.hs | 2 | ||||
-rw-r--r-- | compiler/coreSyn/CoreUtils.hs | 2 | ||||
-rw-r--r-- | compiler/ghci/ByteCodeGen.hs | 2 | ||||
-rw-r--r-- | compiler/prelude/TysPrim.hs | 2 | ||||
-rw-r--r-- | compiler/simplCore/OccurAnal.hs | 2 | ||||
-rw-r--r-- | compiler/simplCore/SetLevels.hs | 16 | ||||
-rw-r--r-- | compiler/simplCore/Simplify.hs | 2 | ||||
-rw-r--r-- | compiler/stranal/DmdAnal.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcEvidence.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcMatches.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcRnTypes.hs | 2 | ||||
-rw-r--r-- | compiler/typecheck/TcSimplify.hs | 2 | ||||
-rw-r--r-- | compiler/types/Unify.hs | 2 | ||||
-rw-r--r-- | compiler/vectorise/Vectorise.hs | 2 |
16 files changed, 23 insertions, 23 deletions
diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 1d90ac0b50..0e02809d61 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1112,7 +1112,7 @@ unboxed thing to f, and have it reboxed in the error cases....] However we *don't* want to do this when the argument is not actually taken apart in the function at all. Otherwise we risk decomposing a -masssive tuple which is barely used. Example: +massive tuple which is barely used. Example: f :: ((Int,Int) -> String) -> (Int,Int) -> a f g pr = error (g pr) diff --git a/compiler/cmm/CmmSink.hs b/compiler/cmm/CmmSink.hs index afa77d5bc4..eb8eedb8e2 100644 --- a/compiler/cmm/CmmSink.hs +++ b/compiler/cmm/CmmSink.hs @@ -336,7 +336,7 @@ shouldSink _ _other = Nothing -- -- discard dead assignments. This doesn't do as good a job as --- removeDeadAsssignments, because it would need multiple passes +-- removeDeadAssignments, because it would need multiple passes -- to get all the dead code, but it catches the common case of -- superfluous reloads from the stack that the stack allocator -- leaves behind. diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs index 3a615f750f..a76b8cc0a0 100644 --- a/compiler/codeGen/StgCmmCon.hs +++ b/compiler/codeGen/StgCmmCon.hs @@ -174,7 +174,7 @@ Now for @Char@-like closures. We generate an assignment of the address of the closure to a temporary. It would be possible simply to generate no code, and record the addressing mode in the environment, but we'd have to be careful if the argument wasn't a constant --- so -for simplicity we just always asssign to a temporary. +for simplicity we just always assign to a temporary. Last special case: @Int@-like closures. We only special-case the situation in which the argument is a literal in the range diff --git a/compiler/coreSyn/CoreUtils.hs b/compiler/coreSyn/CoreUtils.hs index 4a9e136e5c..7896382384 100644 --- a/compiler/coreSyn/CoreUtils.hs +++ b/compiler/coreSyn/CoreUtils.hs @@ -639,7 +639,7 @@ refineDefaultAlt :: [Unique] -> TyCon -> [Type] -> [AltCon] -- Constructors that cannot match the DEFAULT (if any) -> [CoreAlt] -> (Bool, [CoreAlt]) --- Refine the default alterantive to a DataAlt, +-- Refine the default alternative to a DataAlt, -- if there is a unique way to do so refineDefaultAlt us tycon tys imposs_deflt_cons all_alts | (DEFAULT,_,rhs) : rest_alts <- all_alts diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index f4b224d2a5..854eee28da 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -1660,7 +1660,7 @@ atomPrimRep (AnnVar v) = bcIdPrimRep v atomPrimRep (AnnLit l) = typePrimRep1 (literalType l) -- Trac #12128: --- A case expresssion can be an atom because empty cases evaluate to bottom. +-- A case expression can be an atom because empty cases evaluate to bottom. -- See Note [Empty case alternatives] in coreSyn/CoreSyn.hs atomPrimRep (AnnCase _ _ ty _) = ASSERT(typePrimRep ty == [LiftedRep]) LiftedRep atomPrimRep (AnnCoercion {}) = VoidRep diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs index 98064841c1..df8a380b83 100644 --- a/compiler/prelude/TysPrim.hs +++ b/compiler/prelude/TysPrim.hs @@ -425,7 +425,7 @@ GHC needs to be able to figure out how 'v' is represented at runtime. It expects 'rep' to be form TyConApp rr_dc args where 'rr_dc' is a promoteed data constructor from RuntimeRep. So -now we need to go from 'dc' to the correponding PrimRep. We store this +now we need to go from 'dc' to the corresponding PrimRep. We store this PrimRep in the promoted data constructor itself: see TyCon.promDcRepInfo. -} diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs index 96107fe156..728e4725f8 100644 --- a/compiler/simplCore/OccurAnal.hs +++ b/compiler/simplCore/OccurAnal.hs @@ -1141,7 +1141,7 @@ otherwise), the loop does not unravel nicely. @occAnalUnfolding@ deals with the question of bindings where the Id is marked by an INLINE pragma. For these we record that anything which occurs -in its RHS occurs many times. This pessimistically assumes that ths +in its RHS occurs many times. This pessimistically assumes that this inlined binder also occurs many times in its scope, but if it doesn't we'll catch it next time round. At worst this costs an extra simplifier pass. ToDo: try using the occurrence info for the inline'd binder. diff --git a/compiler/simplCore/SetLevels.hs b/compiler/simplCore/SetLevels.hs index 76ac48bd75..27e5ade4e9 100644 --- a/compiler/simplCore/SetLevels.hs +++ b/compiler/simplCore/SetLevels.hs @@ -461,7 +461,7 @@ lvlCase env scrut_fvs scrut' case_bndr ty alts incd_lvl = incMinorLvl (le_ctxt_lvl env) dest_lvl = maxFvLevel (const True) env scrut_fvs - -- Don't abstact over type variables, hence const True + -- Don't abstract over type variables, hence const True lvl_alt alts_env (con, bs, rhs) = do { rhs' <- lvlMFE new_env True rhs @@ -478,7 +478,7 @@ Consider this: f x vs = case x of { MkT y -> let f vs = ...(case y of I# w -> e)...f.. in f vs -Here we can float the (case y ...) out , because y is sure +Here we can float the (case y ...) out, because y is sure to be evaluated, to give f x vs = case x of { MkT y -> caes y of I# w -> @@ -659,7 +659,7 @@ escape a value lambda (and hence save work), for two reasons: * (Minor) Doing so may turn a dynamic allocation (done by machine instructions) into a static one. Minor because we are assuming - we are not escaping a value lambda + we are not escaping a value lambda. But do not so if: - the context is a strict, and @@ -699,7 +699,7 @@ Exammples: we don't (see the use of idStrictness in lvlApp). It's not clear if this test is worth the bother: it's only about CAFs! -It's controlled by a flag (floatConsts) , because doing this too +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.] @@ -745,7 +745,7 @@ we'd like to float the call to error, to get * Bottoming floats (1): Furthermore, we want to float a bottoming expression even if it has free variables: f = \x. g (let v = h x in error ("urk" ++ v)) - Then we'd like to abstact over 'x' can float the whole arg of g: + Then we'd like to abstract over 'x' can float the whole arg of g: lvl = \x. let v = h x in error ("urk" ++ v) f = \x. g (lvl x) To achieve this we pass is_bot to destLevel @@ -798,7 +798,7 @@ in exchange we build a thunk, which is bad. This case reduces allocation by 7% in spectral/puzzle (a rather strange benchmark) and 1.2% in real/fem. Doesn't change any other allocation at all. -We will make a separate decision for the scrutinees and alterantives. +We will make a separate decision for the scrutinees and alternatives. Note [Join points and MFEs] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1144,7 +1144,7 @@ lvlFloatRhs abs_vars dest_lvl env rec mb_join_arity rhs ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When float the RHS of a let-binding, we don't always want to apply lvlMFE to the body of a lambda, as we usually do, because the entire -binding body is already going to the right place (dest_lvl) +binding body is already going to the right place (dest_lvl). A particular example is the top level. Consider concat = /\ a -> foldr ..a.. (++) [] @@ -1165,7 +1165,7 @@ But we must be careful! If we had we /would/ want to float that (factorial 20) out! Functions are treated differently: see the use of isFunction in the calls to destLevel. If there are only type lambdas, then destLevel will say "go to top, and -abstract over the free tyars" and we don't want that here. +abstract over the free tyvars" and we don't want that here. Conclusion: use lvlMFE if there are any value lambdas, lvlExpr otherwise. A little subtle, and I got it wrong to start with. diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 7b684f95fd..a6dbfc1ed4 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -2893,7 +2893,7 @@ So instead we do both: we pass 'c' and 'c#' , and record in c's inlining Absence analysis may later discard 'c'. NB: take great care when doing strictness analysis; - see Note [Lamba-bound unfoldings] in DmdAnal. + see Note [Lambda-bound unfoldings] in DmdAnal. Also note that we can still end up passing stuff that isn't used. Before strictness analysis we have diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 212767e531..ee56d85c44 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -1019,7 +1019,7 @@ mentioned in the (unsound) strictness signature, conservatively approximate the demand put on them (topDmd), and add that to the "lazy_fv" returned by "dmdFix". -Note [Lamba-bound unfoldings] +Note [Lambda-bound unfoldings] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We allow a lambda-bound variable to carry an unfolding, a facility that is used exclusively for join points; see Note [Case binders and join points]. If so, diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs index 60a838bf78..c12fd9a576 100644 --- a/compiler/typecheck/TcEvidence.hs +++ b/compiler/typecheck/TcEvidence.hs @@ -593,7 +593,7 @@ Conceptually, this class has infinitely many instances: ... In practice, we solve `KnownNat` predicates in the type-checker -(see typecheck/TcInteract.hs) because we can't have infinately many instances. +(see typecheck/TcInteract.hs) because we can't have infinitely many instances. The evidence (aka "dictionary") for `KnownNat` is of the form `EvLit (EvNum n)`. We make the following assumptions about dictionaries in GHC: diff --git a/compiler/typecheck/TcMatches.hs b/compiler/typecheck/TcMatches.hs index fcb48ce512..23950c20ba 100644 --- a/compiler/typecheck/TcMatches.hs +++ b/compiler/typecheck/TcMatches.hs @@ -237,7 +237,7 @@ tcMatch ctxt pat_tys rhs_ty match tc_grhss _ (Just {}) _ _ = panic "tc_ghrss" -- Rejected by renamer - -- For (\x -> e), tcExpr has already said "In the expresssion \x->e" + -- For (\x -> e), tcExpr has already said "In the expression \x->e" -- so we don't want to add "In the lambda abstraction \x->e" add_match_ctxt match thing_inside = case mc_what ctxt of diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index 766119635f..31c6dae731 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -3050,7 +3050,7 @@ data CtOrigin -- actual desugaring to MonadFail.fail is live. | Shouldn'tHappenOrigin String -- the user should never see this one, - -- unlesss ImpredicativeTypes is on, where all + -- unless ImpredicativeTypes is on, where all -- bets are off | InstProvidedOrigin Module ClsInst -- Skolem variable arose when we were testing if an instance diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index d13f9e50cc..a4d5325b4c 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -1971,7 +1971,7 @@ to beta[1], and that means the (a ~ beta[1]) will be stuck, as it should be. applyDefaultingRules :: WantedConstraints -> TcS Bool -- True <=> I did some defaulting, by unifying a meta-tyvar --- Imput WantedConstraints are not necessarily zonked +-- Input WantedConstraints are not necessarily zonked applyDefaultingRules wanteds | isEmptyWC wanteds diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index c2f2141e9e..0ee895a4ba 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -574,7 +574,7 @@ a substitution to make two types say True to eqType. NB: eqType is itself not purely syntactic; it accounts for CastTys; see Note [Non-trivial definitional equality] in TyCoRep -Unlike the "impure unifers" in the typechecker (the eager unifier in +Unlike the "impure unifiers" in the typechecker (the eager unifier in TcUnify, and the constraint solver itself in TcCanonical), the pure unifier It does /not/ work up to ~. diff --git a/compiler/vectorise/Vectorise.hs b/compiler/vectorise/Vectorise.hs index d5d24b6b1a..2e09adbbbe 100644 --- a/compiler/vectorise/Vectorise.hs +++ b/compiler/vectorise/Vectorise.hs @@ -71,7 +71,7 @@ vectModule guts@(ModGuts { mg_tcs = tycons -- Vectorise the type environment. This will add vectorised -- type constructors, their representations, and the - -- conrresponding data constructors. Moreover, we produce + -- corresponding data constructors. Moreover, we produce -- bindings for dfuns and family instances of the classes -- and type families used in the DPH library to represent -- array types. |