diff options
author | Gabor Greif <ggreif@gmail.com> | 2017-09-25 12:31:12 +0200 |
---|---|---|
committer | Gabor Greif <ggreif@gmail.com> | 2017-09-26 11:13:14 +0200 |
commit | 7446c7f68bd5addd2f2db0d8d5910fb963869c47 (patch) | |
tree | 05ecf5d25cdecb2893424cd07b0e7002b32ea2c4 | |
parent | 2f8e6e7f8696213b95e3461224909c3b2ec4f7aa (diff) | |
download | haskell-7446c7f68bd5addd2f2db0d8d5910fb963869c47.tar.gz |
A bunch of typofixes
54 files changed, 68 insertions, 68 deletions
diff --git a/compiler/basicTypes/Id.hs b/compiler/basicTypes/Id.hs index 7da61f8484..e1902ff853 100644 --- a/compiler/basicTypes/Id.hs +++ b/compiler/basicTypes/Id.hs @@ -203,7 +203,7 @@ setIdNotExported :: Id -> Id setIdNotExported = Var.setIdNotExported localiseId :: Id -> Id --- Make an with the same unique and type as the +-- Make an Id with the same unique and type as the -- incoming Id, but with an *Internal* Name and *LocalId* flavour localiseId id | ASSERT( isId id ) isLocalId id && isInternalName name diff --git a/compiler/cmm/CmmContFlowOpt.hs b/compiler/cmm/CmmContFlowOpt.hs index 7e1689fdd5..5f34a913d6 100644 --- a/compiler/cmm/CmmContFlowOpt.hs +++ b/compiler/cmm/CmmContFlowOpt.hs @@ -55,7 +55,7 @@ import Control.Monad -- -- This optimisation does three things: -- --- - If a block finishes in an unconditonal branch to another block +-- - If a block finishes in an unconditional branch to another block -- and that is the only jump to that block we concatenate the -- destination block at the end of the current one. -- diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index 6bbcda9fe3..9333d0fcf8 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -346,7 +346,7 @@ In particular, scrutinee variables `x` in expressions of the form "wild_". These "wild" variables may appear in the body of the case-expression, and further, may be shadowed within the body. -So the Unique in an Var is not really unique at all. Still, it's very +So the Unique in a Var is not really unique at all. Still, it's very useful to give a constant-time equality/ordering for Vars, and to give a key that can be used to make sets of Vars (VarSet), or mappings from Vars to other things (VarEnv). Moreover, if you do want to eliminate diff --git a/compiler/coreSyn/CoreUnfold.hs b/compiler/coreSyn/CoreUnfold.hs index fd5a23349a..c459fd2941 100644 --- a/compiler/coreSyn/CoreUnfold.hs +++ b/compiler/coreSyn/CoreUnfold.hs @@ -945,7 +945,7 @@ In a function application (f a b) Code for manipulating sizes -} --- | The size of an candidate expression for unfolding +-- | The size of a candidate expression for unfolding data ExprSize = TooBig | SizeIs { _es_size_is :: {-# UNPACK #-} !Int -- ^ Size found diff --git a/compiler/deSugar/DsCCall.hs b/compiler/deSugar/DsCCall.hs index 64ab9dfe80..7a634ac1ff 100644 --- a/compiler/deSugar/DsCCall.hs +++ b/compiler/deSugar/DsCCall.hs @@ -204,7 +204,7 @@ boxResult :: Type -- Takes the result of the user-level ccall: -- either (IO t), --- or maybe just t for an side-effect-free call +-- or maybe just t for a side-effect-free call -- Returns a wrapper for the primitive ccall itself, along with the -- type of the result of the primitive ccall. This result type -- will be of the form diff --git a/compiler/ghci/GHCi.hs b/compiler/ghci/GHCi.hs index c9d8fe351e..472f0857cb 100644 --- a/compiler/ghci/GHCi.hs +++ b/compiler/ghci/GHCi.hs @@ -560,7 +560,7 @@ We have the following ways to reference things in GHCi: HValue ------ -HValue is a direct reference to an value in the local heap. Obviously +HValue is a direct reference to a value in the local heap. Obviously we cannot use this to refer to things in the external process. diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs index 6648cda42a..0dc5dd08ba 100644 --- a/compiler/hsSyn/HsBinds.hs +++ b/compiler/hsSyn/HsBinds.hs @@ -975,7 +975,7 @@ data TcSpecPrag Id HsWrapper InlinePragma - -- ^ The Id to be specialised, an wrapper that specialises the + -- ^ The Id to be specialised, a wrapper that specialises the -- polymorphic function, and inlining spec for the specialised function deriving Data diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 191ebbf368..c047343c2d 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -87,7 +87,7 @@ infixl 3 &&& -- | A binding top-level 'Name' in an interface file (e.g. the name of an -- 'IfaceDecl'). type IfaceTopBndr = Name - -- It's convenient to have an Name in the IfaceSyn, although in each + -- It's convenient to have a Name in the IfaceSyn, although in each -- case the namespace is implied by the context. However, having an -- Name makes things like ifaceDeclImplicitBndrs and ifaceDeclFingerprints -- very convenient. Moreover, having the key of the binder means that diff --git a/compiler/llvmGen/Llvm/AbsSyn.hs b/compiler/llvmGen/Llvm/AbsSyn.hs index a748ac5657..a89ee35706 100644 --- a/compiler/llvmGen/Llvm/AbsSyn.hs +++ b/compiler/llvmGen/Llvm/AbsSyn.hs @@ -108,7 +108,7 @@ data LlvmAtomicOp -- | Llvm Statements data LlvmStatement {- | - Assign an expression to an variable: + Assign an expression to a variable: * dest: Variable to assign to * source: Source expression -} @@ -260,7 +260,7 @@ data LlvmExpression | ALoad LlvmSyncOrdering SingleThreaded LlvmVar {- | - Navigate in an structure, selecting elements + Navigate in a structure, selecting elements * inbound: Is the pointer inbounds? (computed pointer doesn't overflow) * ptr: Location of the structure * indexes: A list of indexes to select the correct value. diff --git a/compiler/main/InteractiveEval.hs b/compiler/main/InteractiveEval.hs index c6b5e22367..e63d6e3a95 100644 --- a/compiler/main/InteractiveEval.hs +++ b/compiler/main/InteractiveEval.hs @@ -840,7 +840,7 @@ typeKind normalise str = withSession $ \hsc_env -> do liftIO $ hscKcType hsc_env normalise str ----------------------------------------------------------------------------- --- Compile an expression, run it and deliver the result +-- Compile an expression, run it, and deliver the result -- | Parse an expression, the parsed expression can be further processed and -- passed to compileParsedExpr. @@ -848,19 +848,19 @@ parseExpr :: GhcMonad m => String -> m (LHsExpr GhcPs) parseExpr expr = withSession $ \hsc_env -> do liftIO $ runInteractiveHsc hsc_env $ hscParseExpr expr --- | Compile an expression, run it and deliver the resulting HValue. +-- | Compile an expression, run it, and deliver the resulting HValue. compileExpr :: GhcMonad m => String -> m HValue compileExpr expr = do parsed_expr <- parseExpr expr compileParsedExpr parsed_expr --- | Compile an expression, run it and deliver the resulting HValue. +-- | Compile an expression, run it, and deliver the resulting HValue. compileExprRemote :: GhcMonad m => String -> m ForeignHValue compileExprRemote expr = do parsed_expr <- parseExpr expr compileParsedExprRemote parsed_expr --- | Compile an parsed expression (before renaming), run it and deliver +-- | Compile a parsed expression (before renaming), run it, and deliver -- the resulting HValue. compileParsedExprRemote :: GhcMonad m => LHsExpr GhcPs -> m ForeignHValue compileParsedExprRemote expr@(L loc _) = withSession $ \hsc_env -> do diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index 46ca4064fb..172e1818fc 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -124,7 +124,7 @@ import Data.Version -- Let @depExposedPackages@ be the transitive closure from @exposedPackages@ of -- their dependencies. -- --- * When searching for a module from an preload import declaration, +-- * When searching for a module from a preload import declaration, -- only the exposed modules in @exposedPackages@ are valid. -- -- * When searching for a module from an implicit import, all modules diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index a0d2fb81b4..fd5339180c 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -202,7 +202,7 @@ mkBootTypeEnv exports ids tcs fam_insts globaliseAndTidyId :: Id -> Id --- Takes an LocalId with an External Name, +-- Takes a LocalId with an External Name, -- makes it into a GlobalId -- * unchanged Name (might be Internal or External) -- * unchanged details diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 299238b7a5..d897038ad7 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -720,7 +720,7 @@ data Amode = Amode AddrMode InstrBlock {- -Now, given a tree (the argument to an CmmLoad) that references memory, +Now, given a tree (the argument to a CmmLoad) that references memory, produce a suitable addressing mode. A Rule of the Game (tm) for Amodes: use of the addr bit must diff --git a/compiler/nativeGen/SPARC/CodeGen.hs b/compiler/nativeGen/SPARC/CodeGen.hs index 1a7fbeb54d..04ac75772e 100644 --- a/compiler/nativeGen/SPARC/CodeGen.hs +++ b/compiler/nativeGen/SPARC/CodeGen.hs @@ -163,7 +163,7 @@ stmtToInstrs stmt = do {- -Now, given a tree (the argument to an CmmLoad) that references memory, +Now, given a tree (the argument to a CmmLoad) that references memory, produce a suitable addressing mode. A Rule of the Game (tm) for Amodes: use of the addr bit must diff --git a/compiler/nativeGen/X86/CodeGen.hs b/compiler/nativeGen/X86/CodeGen.hs index e62906d125..029b8e8336 100644 --- a/compiler/nativeGen/X86/CodeGen.hs +++ b/compiler/nativeGen/X86/CodeGen.hs @@ -294,7 +294,7 @@ data Amode = Amode AddrMode InstrBlock {- -Now, given a tree (the argument to an CmmLoad) that references memory, +Now, given a tree (the argument to a CmmLoad) that references memory, produce a suitable addressing mode. A Rule of the Game (tm) for Amodes: use of the addr bit must diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index c0d9898e61..b23762a7e8 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -2005,7 +2005,7 @@ okStmt, okDoStmt, okCompStmt, okParStmt, okPArrStmt :: DynFlags -> HsStmtContext Name -> Stmt GhcPs (Located (body GhcPs)) -> Validity -- Return Nothing if OK, (Just extra) if not ok --- The "extra" is an SDoc that is appended to an generic error message +-- The "extra" is an SDoc that is appended to a generic error message okStmt dflags ctxt stmt = case ctxt of diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index bf09f7261d..ebdda8f62a 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -865,7 +865,7 @@ f when it is inlined. So our conservative plan (implemented by updModeForStableUnfoldings) is this: ------------------------------------------------------------- - When simplifying the RHS of an stable unfolding, set the phase + When simplifying the RHS of a stable unfolding, set the phase to the phase in which the stable unfolding first becomes active ------------------------------------------------------------- @@ -1304,7 +1304,7 @@ ones that are trivial): Note [Stable unfoldings and postInlineUnconditionally] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Do not do postInlineUnconditionally if the Id has an stable unfolding, +Do not do postInlineUnconditionally if the Id has a stable unfolding, otherwise we lose the unfolding. Example -- f has stable unfolding with rhs (e |> co) diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index c73f0f6545..5e596a3fea 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -3068,7 +3068,7 @@ and c is unused. Note [Duplicated env] ~~~~~~~~~~~~~~~~~~~~~ Some of the alternatives are simplified, but have not been turned into a join point -So they *must* have an zapped subst-env. So we can't use completeNonRecX to +So they *must* have a zapped subst-env. So we can't use completeNonRecX to bind the join point, because it might to do PostInlineUnconditionally, and we'd lose that when zapping the subst-env. We could have a per-alt subst-env, but zapping it (as we do in mkDupableCont, the Select case) is safe, and @@ -3329,7 +3329,7 @@ Note [Setting the new unfolding] important: if exprIsConApp says 'yes' for a recursive thing, then we can get into an infinite loop -If there's an stable unfolding on a loop breaker (which happens for +If there's a stable unfolding on a loop breaker (which happens for INLINABLE), we hang on to the inlining. It's pretty dodgy, but the user did say 'INLINE'. May need to revisit this choice. diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index a35309c181..6e896176f9 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -364,7 +364,7 @@ stgCsePairs env0 ((b,e):pairs) mbCons = maybe id (:) -- The RHS of a binding. --- If it is an constructor application, either short-cut it or extend the environment +-- If it is a constructor application, either short-cut it or extend the environment stgCseRhs :: CseEnv -> OutId -> InStgRhs -> (Maybe (OutId, OutStgRhs), CseEnv) stgCseRhs env bndr (StgRhsCon ccs dataCon args) | Just other_bndr <- envLookup dataCon args' env diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs index 252f18b983..28b0df3404 100644 --- a/compiler/stranal/WorkWrap.hs +++ b/compiler/stranal/WorkWrap.hs @@ -232,7 +232,7 @@ has no wrapper, the worker for g will rebox p. So we get g x y p = case p of (I# p#) -> $wg x y p# -Now, in this case the reboxing will float into the True branch, an so +Now, in this case the reboxing will float into the True branch, and so the allocation will only happen on the error path. But it won't float inwards if there are multiple branches that call (f p), so the reboxing will happen on every call of g. Disaster. diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index e4936a9251..c8f0b1deef 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -239,7 +239,7 @@ improveClsFD clas_tvs fd -- for fundep (x,y -> p,q) from class (C x p y q) -- If (sx,sy) unifies with (tx,ty), take the subst S --- 'qtvs' are the quantified type variables, the ones which an be instantiated +-- 'qtvs' are the quantified type variables, the ones which can be instantiated -- to make the types match. For example, given -- class C a b | a->b where ... -- instance C (Maybe x) (Tree x) where .. @@ -645,7 +645,7 @@ checkFunDeps inst_envs (ClsInst { is_tvs = qtvs1, is_cls = cls | otherwise = Skolem eq_inst i1 i2 = instanceDFunId i1 == instanceDFunId i2 - -- An single instance may appear twice in the un-nubbed conflict list + -- A single instance may appear twice in the un-nubbed conflict list -- because it may conflict with more than one fundep. E.g. -- class C a b c | a -> b, a -> c -- instance C Int Bool Bool diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 155aee85ce..77a313bcb1 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -867,7 +867,7 @@ kind parameters. Consider this code (also from Trac #11732): newtype Fun a b = Fun (a -> b) deriving (Cat k) -Even though we requested an derived instance of the form (Cat k Fun), the +Even though we requested a derived instance of the form (Cat k Fun), the kind unification will actually generate (Cat * Fun) (i.e., the same thing as if the user wrote deriving (Cat *)). diff --git a/compiler/typecheck/TcEnv.hs b/compiler/typecheck/TcEnv.hs index e8ddd0702d..21b895eea3 100644 --- a/compiler/typecheck/TcEnv.hs +++ b/compiler/typecheck/TcEnv.hs @@ -829,7 +829,7 @@ default the 'a' to (), rather than to Integer (which is what would otherwise hap and then GHCi doesn't attempt to print the (). So in interactive mode, we add () to the list of defaulting types. See Trac #1200. -Additonally, the list type [] is added as a default specialization for +Additionally, the list type [] is added as a default specialization for Traversable and Foldable. As such the default default list now has types of varying kinds, e.g. ([] :: * -> *) and (Integer :: *). diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index dc7416103b..4c992e11c7 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -1196,7 +1196,7 @@ Answer: * When we make a superclass selection from InstSkol we use a SkolemInfo of (InstSC size), where 'size' is the size of - the constraint whose superclass we are taking. An similarly + the constraint whose superclass we are taking. A similarly when taking the superclass of an InstSC. This is implemented in TcCanonical.newSCWorkFromFlavored diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index c581a88768..21765a67b9 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -13,7 +13,7 @@ around. This is done to allow the environment to be manipulated in a stack like fashion when entering expressions... ect. For state that is global and should be returned at the end (e.g not part -of the stack mechanism), you should use an TcRef (= IORef) to store them. +of the stack mechanism), you should use a TcRef (= IORef) to store them. -} {-# LANGUAGE CPP, ExistentialQuantification, GeneralizedNewtypeDeriving, @@ -2902,7 +2902,7 @@ level. equalities involving type functions. Example: Assume we have a wanted at depth 7: [W] d{7} : F () ~ a - If there is an type function equation "F () = Int", this would be rewritten to + If there is a type function equation "F () = Int", this would be rewritten to [W] d{8} : Int ~ a and remembered as having depth 8. diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 8cfb88cf26..bcd26bbc46 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -1029,7 +1029,7 @@ The same idea is sometimes also called "saturation"; find all the equalities that must hold in any solution. Or, equivalently, you can think of the derived shadows as implementing -the "model": an non-idempotent but no-occurs-check substitution, +the "model": a non-idempotent but no-occurs-check substitution, reflecting *all* *Nominal* equalities (a ~N ty) that are not immediately soluble by unification. diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index b479412e83..f2b60dece3 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1010,7 +1010,7 @@ tcDataDefn roles_info ; return tycon } where -- In hs-boot, a 'data' declaration with no constructors - -- indicates an nominally distinct abstract data type. + -- indicates a nominally distinct abstract data type. mk_tc_rhs HsBootFile _ [] = return AbstractTyCon diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 5c5ed7f781..712f9ad78b 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -151,7 +151,7 @@ The nested forall is ambiguous. Originally we called checkAmbiguity in the forall case of check_type, but that had two bad consequences: * We got two error messages about (Eq b) in a nested forall like this: g :: forall a. Eq a => forall b. Eq b => a -> a - * If we try to check for ambiguity of an nested forall like + * If we try to check for ambiguity of a nested forall like (forall a. Eq a => b), the implication constraint doesn't bind all the skolems, which results in "No skolem info" in error messages (see Trac #10432). diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index 9147c1f7b0..39d2e9b8c7 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -1666,7 +1666,7 @@ isAbstractTyCon :: TyCon -> Bool isAbstractTyCon (AlgTyCon { algTcRhs = AbstractTyCon }) = True isAbstractTyCon _ = False --- | Make an fake, recovery 'TyCon' from an existing one. +-- | Make a fake, recovery 'TyCon' from an existing one. -- Used when recovering from errors makeRecoveryTyCon :: TyCon -> TyCon makeRecoveryTyCon tc diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index 5fba83fef5..457d012504 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -394,7 +394,7 @@ tcUnifyTyKis bind_fn tys1 tys2 type UnifyResult = UnifyResultM TCvSubst data UnifyResultM a = Unifiable a -- the subst that unifies the types | MaybeApart a -- the subst has as much as we know - -- it must be part of an most general unifier + -- it must be part of a most general unifier -- See Note [The substitution in MaybeApart] | SurelyApart deriving Functor @@ -711,7 +711,7 @@ Consider this: type instance Foo MkG = False We would like that to be accepted. For that to work, we need to introduce -a coercion variable on the left an then use it on the right. Accordingly, +a coercion variable on the left and then use it on the right. Accordingly, at use sites of Foo, we need to be able to use matching to figure out the value for the coercion. (See the desugared version: diff --git a/compiler/utils/EnumSet.hs b/compiler/utils/EnumSet.hs index 99b93f5c22..670a5c64c8 100644 --- a/compiler/utils/EnumSet.hs +++ b/compiler/utils/EnumSet.hs @@ -1,4 +1,4 @@ --- | An tiny wrapper around 'IntSet.IntSet' for representing sets of 'Enum' +-- | A tiny wrapper around 'IntSet.IntSet' for representing sets of 'Enum' -- things. module EnumSet ( EnumSet diff --git a/compiler/utils/Panic.hs b/compiler/utils/Panic.hs index 910906e08c..ebf830385c 100644 --- a/compiler/utils/Panic.hs +++ b/compiler/utils/Panic.hs @@ -196,7 +196,7 @@ sorryDoc x doc = throwGhcException (PprSorry x doc) pgmErrorDoc x doc = throwGhcException (PprProgramError x doc) --- | Throw an failed assertion exception for a given filename and line number. +-- | Throw a failed assertion exception for a given filename and line number. assertPanic :: String -> Int -> a assertPanic file line = Exception.throw (Exception.AssertionFailed diff --git a/docs/ghci/ghci.tex b/docs/ghci/ghci.tex index c4638a6719..e4fbb0b771 100644 --- a/docs/ghci/ghci.tex +++ b/docs/ghci/ghci.tex @@ -458,9 +458,9 @@ date. There are three parts to it: \item {\bf Package Symbol Table (PST)} @:: FiniteMap Module ModDetails@ - Adding an package interface to PIT doesn't make it directly usable + Adding a package interface to PIT doesn't make it directly usable to @compile@, because it first needs to be wired (renamed + - typechecked) into the sphagetti of the HST. On the other hand, + typechecked) into the spaghetti of the HST. On the other hand, most modules only use a few entities from any imported interface, so wiring-in the interface at PIT-entry time might be a big time waster. Also, wiring in an interface could mean reading other @@ -886,14 +886,14 @@ trees in the GHCI heap. References from other modules to these entities is direct -- when you have a @TyCon@ in your hand, you really have a pointer directly to the @TyCon@ structure in the defining module, rather than some kind of index into a global symbol table. So there -is a global symbol table, but it has a distributed (sphagetti-like?) +is a global symbol table, but it has a distributed (spaghetti-like?) nature. This gives fast and convenient access to tycon, class, instance, etc, information. But because there are no levels of indirection, there's a problem when we replace @M@ with an updated version of @M@. We then need to find all references to entities in the old @M@'s -sphagetti, and replace them with pointers to the new @M@'s sphagetti. +spaghetti, and replace them with pointers to the new @M@'s spaghetti. This problem motivates a large part of the design. diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index edfee6c7ee..9402885774 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -8868,7 +8868,7 @@ you must ``import Data.Kind`` to get ``*`` (but only with :ghc-flag:`-XTypeInTyp enabled). The only way ``*`` is unordinary is in its parsing. In order to be backward -compatible, ``*`` is parsed as if it were an alphanumeric idenfifier; note +compatible, ``*`` is parsed as if it were an alphanumeric identifier; note that we do not write ``Int :: (*)`` but just plain ``Int :: *``. Due to the bizarreness with which ``*`` is parsed--and the fact that it is the only such operator in GHC--there are some corner cases that are @@ -12189,7 +12189,7 @@ A simple example of the new notation is the expression :: We call this a procedure or arrow abstraction. As with a lambda expression, the variable ``x`` is a new variable bound within the ``proc``-expression. It refers to the input to the arrow. In the above -example, ``-<`` is not an identifier but an new reserved symbol used for +example, ``-<`` is not an identifier but a new reserved symbol used for building commands from an expression of arrow type and an expression to be fed as input to that arrow. (The weird look will make more sense later.) It may be read as analogue of application for arrows. The above diff --git a/docs/users_guide/safe_haskell.rst b/docs/users_guide/safe_haskell.rst index 7be442e036..6b32826235 100644 --- a/docs/users_guide/safe_haskell.rst +++ b/docs/users_guide/safe_haskell.rst @@ -358,7 +358,7 @@ imported module ``N`` changing the behaviour of existing code. For example, if the second condition isn't violated, then the module author ``M`` must depend either on a type-class or type defined in ``N``. -When an particular type-class method call is considered unsafe due to +When a particular type-class method call is considered unsafe due to overlapping instances, and the module being compiled is using :ghc-flag:`-XSafe` or :ghc-flag:`-XTrustworthy`, then compilation will fail. For :ghc-flag:`-XUnsafe`, no restriction is applied, and for modules using safe inference, they will diff --git a/docs/users_guide/separate_compilation.rst b/docs/users_guide/separate_compilation.rst index 29ee7bb1aa..0de5eb59cd 100644 --- a/docs/users_guide/separate_compilation.rst +++ b/docs/users_guide/separate_compilation.rst @@ -650,7 +650,7 @@ There are several points to note here: - Just as compiling ``A.hs`` produces an interface file ``A.hi``, and an object file ``A.o``, so compiling ``A.hs-boot`` produces an - interface file ``A.hi-boot``, and an pseudo-object file ``A.o-boot``: + interface file ``A.hi-boot``, and a pseudo-object file ``A.o-boot``: - The pseudo-object file ``A.o-boot`` is empty (don't link it!), but it is very useful when using a Makefile, to record when the diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index da2ea3d18f..1fc388040c 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -241,7 +241,7 @@ class Eq a => Bits a where x `shiftR` i = x `shift` (-i) {-| Shift the first argument right by the specified number of bits, which - must be non-negative an smaller than the number of bits in the type. + must be non-negative and smaller than the number of bits in the type. Right shifts perform sign extension on signed number types; i.e. they fill the top bits with 1 if the @x@ is negative diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 3d257e0f17..e22f7cb082 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -793,7 +793,7 @@ mkRealConstr dt f = case datarep dt of FloatRep -> mkPrimCon dt (show f) (FloatConstr (toRational f)) _ -> errorWithoutStackTrace $ "Data.Data.mkRealConstr is not supported for " ++ dataTypeName dt ++ - ", as it is not an Real data type." + ", as it is not a Real data type." -- | Makes a constructor for 'Char'. mkCharConstr :: DataType -> Char -> Constr diff --git a/libraries/base/GHC/Event/PSQ.hs b/libraries/base/GHC/Event/PSQ.hs index 976ffe16b3..07b8de614b 100644 --- a/libraries/base/GHC/Event/PSQ.hs +++ b/libraries/base/GHC/Event/PSQ.hs @@ -58,7 +58,7 @@ import GHC.Types (Int) {- -- Use macros to define strictness of functions. --- STRICT_x_OF_y denotes an y-ary function strict in the x-th parameter. +-- STRICT_x_OF_y denotes a y-ary function strict in the x-th parameter. -- We do not use BangPatterns, because they are not in any standard and we -- want the compilers to be compiled by as many compilers as possible. #define STRICT_1_OF_2(fn) fn arg _ | arg `seq` False = undefined diff --git a/libraries/base/GHC/Show.hs b/libraries/base/GHC/Show.hs index 75080b3c90..980b4a7d85 100644 --- a/libraries/base/GHC/Show.hs +++ b/libraries/base/GHC/Show.hs @@ -469,7 +469,7 @@ instance Show Integer where | otherwise = integerToString n r showList = showList__ (showsPrec 0) --- Divide an conquer implementation of string conversion +-- Divide and conquer implementation of string conversion integerToString :: Integer -> String -> String integerToString n0 cs0 | n0 < 0 = '-' : integerToString' (- n0) cs0 diff --git a/libraries/base/cbits/primFloat.c b/libraries/base/cbits/primFloat.c index f0746775d3..dde5d06503 100644 --- a/libraries/base/cbits/primFloat.c +++ b/libraries/base/cbits/primFloat.c @@ -315,7 +315,7 @@ rintFloat(HsFloat f) mant += 2*half; if (mant == FLT_POWER2) { - /* next power of 2, increase exponent an set mantissa to 0 */ + /* next power of 2, increase exponent and set mantissa to 0 */ u.ieee.mantissa = 0; u.ieee.exponent += 1; return u.f; diff --git a/libraries/integer-simple/GHC/Integer.hs b/libraries/integer-simple/GHC/Integer.hs index f419b2f592..a519acea9a 100644 --- a/libraries/integer-simple/GHC/Integer.hs +++ b/libraries/integer-simple/GHC/Integer.hs @@ -11,7 +11,7 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- An simple definition of the 'Integer' type. +-- A simple definition of the 'Integer' type. -- ----------------------------------------------------------------------------- diff --git a/libraries/integer-simple/GHC/Integer/Simple/Internals.hs b/libraries/integer-simple/GHC/Integer/Simple/Internals.hs index 64d0d6fd79..50733d4c0e 100644 --- a/libraries/integer-simple/GHC/Integer/Simple/Internals.hs +++ b/libraries/integer-simple/GHC/Integer/Simple/Internals.hs @@ -11,7 +11,7 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- An simple definition of the 'Integer' type. +-- A simple definition of the 'Integer' type. -- ----------------------------------------------------------------------------- diff --git a/libraries/integer-simple/GHC/Integer/Type.hs b/libraries/integer-simple/GHC/Integer/Type.hs index 31f852bbd1..cabdfe5a53 100644 --- a/libraries/integer-simple/GHC/Integer/Type.hs +++ b/libraries/integer-simple/GHC/Integer/Type.hs @@ -18,7 +18,7 @@ -- Stability : internal -- Portability : non-portable (GHC Extensions) -- --- An simple definition of the 'Integer' type. +-- A simple definition of the 'Integer' type. -- ----------------------------------------------------------------------------- diff --git a/libraries/integer-simple/integer-simple.cabal b/libraries/integer-simple/integer-simple.cabal index 0c05ad71ec..231619c6c7 100644 --- a/libraries/integer-simple/integer-simple.cabal +++ b/libraries/integer-simple/integer-simple.cabal @@ -6,7 +6,7 @@ license-file: LICENSE maintainer: igloo@earth.li synopsis: Simple Integer library description: - This package contains an simple Integer library. + This package contains a simple Integer library. cabal-version: >=1.10 build-type: Simple diff --git a/rts/Capability.c b/rts/Capability.c index 1023be87ec..0fcb0c99e1 100644 --- a/rts/Capability.c +++ b/rts/Capability.c @@ -10,7 +10,7 @@ * STG execution, a pointer to the capabilitity is kept in a * register (BaseReg; actually it is a pointer to cap->r). * - * Only in an THREADED_RTS build will there be multiple capabilities, + * Only in a THREADED_RTS build will there be multiple capabilities, * for non-threaded builds there is only one global capability, namely * MainCapability. * diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 6047b49aca..4d54ecf6dc 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -1742,7 +1742,7 @@ loop: ccall tryWakeupThread(MyCapability() "ptr", tso); - // If it was an readMVar, then we can still do work, + // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) if (why_blocked == BlockedOnMVarRead) { q = StgMVarTSOQueue_link(q); @@ -1823,7 +1823,7 @@ loop: ccall tryWakeupThread(MyCapability() "ptr", tso); - // If it was an readMVar, then we can still do work, + // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) if (why_blocked == BlockedOnMVarRead) { q = StgMVarTSOQueue_link(q); diff --git a/rts/Threads.c b/rts/Threads.c index c87551180b..836cdd6048 100644 --- a/rts/Threads.c +++ b/rts/Threads.c @@ -808,7 +808,7 @@ loop: tryWakeupThread(cap, tso); - // If it was an readMVar, then we can still do work, + // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) if (why_blocked == BlockedOnMVarRead) { q = ((StgMVarTSOQueue*)q)->link; diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index ffaed5f17c..6c5a73310c 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -315,7 +315,7 @@ freeStorage (bool free_heap) - pushes an update frame pointing to the CAF_BLACKHOLE - Why do we build an BLACKHOLE in the heap rather than just updating + Why do we build a BLACKHOLE in the heap rather than just updating the thunk directly? It's so that we only need one kind of update frame - otherwise we'd need a static version of the update frame too, and various other parts of the RTS that deal with update diff --git a/testsuite/tests/concurrent/should_run/conc065.hs b/testsuite/tests/concurrent/should_run/conc065.hs index 8f6c18b79d..7e75381a26 100644 --- a/testsuite/tests/concurrent/should_run/conc065.hs +++ b/testsuite/tests/concurrent/should_run/conc065.hs @@ -4,7 +4,7 @@ import Control.Concurrent import Control.Exception -- This loop spends most of its time printing stuff, and very occasionally --- pops outside 'block'. This test ensures that an thread trying to +-- pops outside 'block'. This test ensures that a thread trying to -- throwTo this thread will eventually succeed. loop = mask_ (print "alive") >> loop diff --git a/testsuite/tests/dph/nbody/Generate.hs b/testsuite/tests/dph/nbody/Generate.hs index 808ab8e6bf..5b700ddec5 100644 --- a/testsuite/tests/dph/nbody/Generate.hs +++ b/testsuite/tests/dph/nbody/Generate.hs @@ -70,7 +70,7 @@ genPointsDisc n (originX, originY) radiusMax in originX `seq` originY `seq` U.zipWith makeXY radius angle --- | A point cloud with areas of high an low density +-- | A point cloud with areas of high and low density genPointsCombo :: Int -- ^ number of points -> U.Array (Double, Double) diff --git a/testsuite/tests/dph/quickhull/TestData.hs b/testsuite/tests/dph/quickhull/TestData.hs index a27cca288e..938c9fea91 100644 --- a/testsuite/tests/dph/quickhull/TestData.hs +++ b/testsuite/tests/dph/quickhull/TestData.hs @@ -63,7 +63,7 @@ genPointsDisc n (originX, originY) radiusMax in map makeXY $ zip radius angle --- | A point cloud with areas of high an low density +-- | A point cloud with areas of high and low density genPointsCombo :: Int -- ^ number of points -> [(Double, Double)] diff --git a/testsuite/tests/programs/maessen-hashtab/Data/HashTab.hs b/testsuite/tests/programs/maessen-hashtab/Data/HashTab.hs index e96d5c5efa..85b3046db9 100644 --- a/testsuite/tests/programs/maessen-hashtab/Data/HashTab.hs +++ b/testsuite/tests/programs/maessen-hashtab/Data/HashTab.hs @@ -171,7 +171,7 @@ new cmpr hash = do -- ----------------------------------------------------------------------------- -- Inserting a key\/value pair into the hash table --- | Inserts an key\/value mapping into the hash table. +-- | Inserts a key\/value mapping into the hash table. -- -- Note that 'insert' doesn't remove the old entry from the table - -- the behaviour is like an association list, where 'lookup' returns diff --git a/testsuite/tests/typecheck/should_compile/T12734a.hs b/testsuite/tests/typecheck/should_compile/T12734a.hs index 38f7307f1a..3add59e648 100644 --- a/testsuite/tests/typecheck/should_compile/T12734a.hs +++ b/testsuite/tests/typecheck/should_compile/T12734a.hs @@ -16,7 +16,7 @@ -- This version is shorter than T12734, and should yield a -- type error message. If things go wrong, you get --- an nfinite loop +-- an infinite loop module T12734a where |