diff options
121 files changed, 160 insertions, 160 deletions
diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs index 68b9f00798..1a7db17ccd 100644 --- a/compiler/GHC/Hs/Binds.hs +++ b/compiler/GHC/Hs/Binds.hs @@ -407,7 +407,7 @@ where 'BIND' binds the monomorphic Ids 'fm' and 'gm', means gp = ...same again, with gm instead of fm -The 'fwrap' is an impedence-matcher that typically does nothing; see +The 'fwrap' is an impedance-matcher that typically does nothing; see Note [ABExport wrapper]. This is a pretty bad translation, because it duplicates all the bindings. diff --git a/compiler/GHC/HsToCore/PmCheck.hs b/compiler/GHC/HsToCore/PmCheck.hs index c712055d70..1467ef07f4 100644 --- a/compiler/GHC/HsToCore/PmCheck.hs +++ b/compiler/GHC/HsToCore/PmCheck.hs @@ -947,7 +947,7 @@ Main functions are: * pmCheck :: PatVec -> [PatVec] -> ValVec -> Delta -> DsM PartialResult This function implements functions `covered`, `uncovered` and - `divergent` from the paper at once. Calls out to the auxilary function + `divergent` from the paper at once. Calls out to the auxiliary function `pmCheckGuards` for handling (possibly multiple) guarded RHSs when the whole clause is checked. Slightly different from the paper because it does not even produce the covered and uncovered sets. Since we only care about whether a diff --git a/compiler/GHC/StgToCmm/Bind.hs b/compiler/GHC/StgToCmm/Bind.hs index 9e192a0ac8..d373b79d0c 100644 --- a/compiler/GHC/StgToCmm/Bind.hs +++ b/compiler/GHC/StgToCmm/Bind.hs @@ -180,7 +180,7 @@ cgBind (StgRec pairs) 3. emit all the inits, and then all the bodies We'd rather not have separate functions to do steps 1 and 2 for - each binding, since in pratice they share a lot of code. So we + each binding, since in practice they share a lot of code. So we have just one function, cgRhs, that returns a pair of the CgIdInfo for step 1, and a monadic computation to generate the code in step 2. diff --git a/compiler/GHC/StgToCmm/Prof.hs b/compiler/GHC/StgToCmm/Prof.hs index ce8ef61f17..4743b79622 100644 --- a/compiler/GHC/StgToCmm/Prof.hs +++ b/compiler/GHC/StgToCmm/Prof.hs @@ -328,14 +328,14 @@ ldvEnterClosure :: ClosureInfo -> CmmReg -> FCode () ldvEnterClosure closure_info node_reg = do dflags <- getDynFlags let tag = funTag dflags closure_info - -- don't forget to substract node's tag + -- don't forget to subtract node's tag ldvEnter (cmmOffsetB dflags (CmmReg node_reg) (-tag)) ldvEnter :: CmmExpr -> FCode () -- Argument is a closure pointer ldvEnter cl_ptr = do dflags <- getDynFlags - let -- don't forget to substract node's tag + let -- don't forget to subtract node's tag ldv_wd = ldvWord dflags cl_ptr new_ldv_wd = cmmOrWord dflags (cmmAndWord dflags (CmmLoad ldv_wd (bWord dflags)) (CmmLit (mkWordCLit dflags (iLDV_CREATE_MASK dflags)))) diff --git a/compiler/GHC/ThToHs.hs b/compiler/GHC/ThToHs.hs index ed6238e8de..eb38d36319 100644 --- a/compiler/GHC/ThToHs.hs +++ b/compiler/GHC/ThToHs.hs @@ -1059,7 +1059,7 @@ cvt_tup es boxity = do { let cvtl_maybe Nothing = return missingTupArg (map noLoc es') boxity } -{- Note [Operator assocation] +{- Note [Operator association] We must be quite careful about adding parens: * Infix (UInfix ...) op arg Needs parens round the first arg * Infix (Infix ...) op arg Needs parens round the first arg diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 9fdac2cc8c..19fbce3690 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -618,7 +618,7 @@ useCount _ = Many * * ************************************************************************ -This domain differst from JointDemand in the sence that pure absence +This domain differst from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/basicTypes/IdInfo.hs b/compiler/basicTypes/IdInfo.hs index ab6e08974e..dea309de1a 100644 --- a/compiler/basicTypes/IdInfo.hs +++ b/compiler/basicTypes/IdInfo.hs @@ -402,7 +402,7 @@ But we don't do that for instance declarations and so we just treat them all uniformly. The EXCEPTION is PrimOpIds, which do have rules in their IdInfo. That is -jsut for convenience really. +just for convenience really. However, LocalIds may have non-empty RuleInfo. We treat them differently because: diff --git a/compiler/basicTypes/Literal.hs b/compiler/basicTypes/Literal.hs index 338095566c..1e088a8d1a 100644 --- a/compiler/basicTypes/Literal.hs +++ b/compiler/basicTypes/Literal.hs @@ -180,7 +180,7 @@ They only get converted into real Core, during the CorePrep phase, although TidyPgm looks ahead at what the core will be, so that it can see whether it involves CAFs. -When we initally build an Integer literal, notably when +When we initially build an Integer literal, notably when deserialising it from an interface file (see the Binary instance below), we don't have convenient access to the mkInteger Id. So we just use an error thunk, and fill in the real Id when we do tcIfaceLit diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index 66e39f0d69..9452b5f6c8 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -348,7 +348,7 @@ data ForeignLabelSource -- external packages. It is safe to treat the RTS package as "external". | ForeignLabelInExternalPackage - -- | Label is in the package currenly being compiled. + -- | Label is in the package currently being compiled. -- This is only used for creating hacky tmp labels during code generation. -- Don't use it in any code that might be inlined across a package boundary -- (ie, core code) else the information will be wrong relative to the diff --git a/compiler/cmm/CmmNode.hs b/compiler/cmm/CmmNode.hs index 9d6fa7f29b..1b387020f5 100644 --- a/compiler/cmm/CmmNode.hs +++ b/compiler/cmm/CmmNode.hs @@ -669,7 +669,7 @@ scopeUniques (SubScope u _) = [u] scopeUniques (CombinedScope s1 s2) = scopeUniques s1 ++ scopeUniques s2 -- Equality and order is based on the head uniques defined above. We --- take care to short-cut the (extremly) common cases. +-- take care to short-cut the (extremely) common cases. instance Eq CmmTickScope where GlobalScope == GlobalScope = True GlobalScope == _ = False diff --git a/compiler/cmm/CmmParse.y b/compiler/cmm/CmmParse.y index 3cfb7ecee2..e568378197 100644 --- a/compiler/cmm/CmmParse.y +++ b/compiler/cmm/CmmParse.y @@ -574,7 +574,7 @@ importName :: { (FastString, CLabel) } -- A label imported without an explicit packageId. - -- These are taken to come frome some foreign, unnamed package. + -- These are taken to come from some foreign, unnamed package. : NAME { ($1, mkForeignLabel $1 Nothing ForeignLabelInExternalPackage IsFunction) } diff --git a/compiler/coreSyn/CoreOpt.hs b/compiler/coreSyn/CoreOpt.hs index 4a0322f00c..41a017e8ea 100644 --- a/compiler/coreSyn/CoreOpt.hs +++ b/compiler/coreSyn/CoreOpt.hs @@ -542,7 +542,7 @@ A program has the Let-Unfoldings property iff: - For every let-bound variable f, whether top-level or nested, whether recursive or not: - - Both the binding Id of f, and every occurence Id of f, has an idUnfolding. + - Both the binding Id of f, and every occurrence Id of f, has an idUnfolding. - For non-INLINE things, that unfolding will be f's right hand sids - For INLINE things (which have a "stable" unfolding) that unfolding is semantically equivalent to f's RHS, but derived from the original RHS of f @@ -1226,11 +1226,11 @@ Here we implement the "push rules" from FC papers: (fun |> co) arg and we want to transform it to (fun arg') |> co' - for some suitable co' and tranformed arg'. + for some suitable co' and transformed arg'. * The PushK rule for data constructors. We have (K e1 .. en) |> co - and we want to tranform to + and we want to transform to (K e1' .. en') by pushing the coercion into the arguments -} diff --git a/compiler/coreSyn/CoreSyn.hs b/compiler/coreSyn/CoreSyn.hs index e3ad4715f1..919e2300be 100644 --- a/compiler/coreSyn/CoreSyn.hs +++ b/compiler/coreSyn/CoreSyn.hs @@ -1227,7 +1227,7 @@ notOrphan _ = False chooseOrphanAnchor :: NameSet -> IsOrphan -- Something (rule, instance) is relate to all the Names in this -- list. Choose one of them to be an "anchor" for the orphan. We make --- the choice deterministic to avoid gratuitious changes in the ABI +-- the choice deterministic to avoid gratuitous changes in the ABI -- hash (#4012). Specifically, use lexicographic comparison of -- OccName rather than comparing Uniques -- @@ -1559,7 +1559,7 @@ data UnfoldingGuidance ug_size :: Int, -- The "size" of the unfolding. - ug_res :: Int -- Scrutinee discount: the discount to substract if the thing is in + ug_res :: Int -- Scrutinee discount: the discount to subtract if the thing is in } -- a context (case (thing args) of ...), -- (where there are the right number of arguments.) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index 5ecc4da00e..c2978d8774 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -528,7 +528,7 @@ In the above example, suppose we had {-# RULES "rule-for-g" forally. g [y] = ... #-} Then "rule-for-f" and "rule-for-g" would compete. Better to add phase control, so "rule-for-f" has a chance to fire before "rule-for-g" becomes -active; or perhpas after "rule-for-g" has become inactive. This is checked +active; or perhaps after "rule-for-g" has become inactive. This is checked by 'competesWith' Class methods have a built-in RULE to select the method from the dictionary, diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs index 5290d1a978..c69b1da6e8 100644 --- a/compiler/deSugar/DsMeta.hs +++ b/compiler/deSugar/DsMeta.hs @@ -279,7 +279,7 @@ in repTyClD and repC. Note [Don't quantify implicit type variables in quotes] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If you're not careful, it's suprisingly easy to take this quoted declaration: +If you're not careful, it's surprisingly easy to take this quoted declaration: [d| idProxy :: forall proxy (b :: k). proxy b -> proxy b idProxy x = x @@ -1404,7 +1404,7 @@ repE e@(HsTickPragma {}) = notHandled "Tick Pragma" (ppr e) repE e = notHandled "Expression form" (ppr e) ----------------------------------------------------------------------------- --- Building representations of auxillary structures like Match, Clause, Stmt, +-- Building representations of auxiliary structures like Match, Clause, Stmt, repMatchTup :: LMatch GhcRn (LHsExpr GhcRn) -> DsM (Core TH.MatchQ) repMatchTup (dL->L _ (Match { m_pats = [p] @@ -1481,7 +1481,7 @@ repUpdFields = repList fieldExpQTyConName rep_fld -- shadow each other. Consider: [| do { x <- f 1; x <- f x; g x } |] -- First gensym new names for every variable in any of the patterns. -- both static (x'1 and x'2), and dynamic ((gensym "x") and (gensym "y")) --- if variables didn't shaddow, the static gensym wouldn't be necessary +-- if variables didn't shadow, the static gensym wouldn't be necessary -- and we could reuse the original names (x and x). -- -- do { x'1 <- gensym "x" diff --git a/compiler/deSugar/DsMonad.hs b/compiler/deSugar/DsMonad.hs index 5090bc8d81..2329a92d28 100644 --- a/compiler/deSugar/DsMonad.hs +++ b/compiler/deSugar/DsMonad.hs @@ -530,7 +530,7 @@ dsExtendMetaEnv menv thing_inside discardWarningsDs :: DsM a -> DsM a -- Ignore warnings inside the thing inside; --- used to ignore inaccessable cases etc. inside generated code +-- used to ignore inaccessible cases etc. inside generated code discardWarningsDs thing_inside = do { env <- getGblEnv ; old_msgs <- readTcRef (ds_msgs env) diff --git a/compiler/hieFile/HieAst.hs b/compiler/hieFile/HieAst.hs index 50b4422e64..c62ab0ae83 100644 --- a/compiler/hieFile/HieAst.hs +++ b/compiler/hieFile/HieAst.hs @@ -402,7 +402,7 @@ bar (x :: forall a. a -> a) = ... -- a is not in scope here bax (x :: a) = ... -- a is in scope here Because of HsWC and HsIB pass on their scope to their children we must wrap the LHsType in pattern signatures in a -Shielded explictly, so that the HsWC/HsIB scope is not passed +Shielded explicitly, so that the HsWC/HsIB scope is not passed on the the LHsType -} diff --git a/compiler/hieFile/HieBin.hs b/compiler/hieFile/HieBin.hs index a0d0881d9e..0a5d60df92 100644 --- a/compiler/hieFile/HieBin.hs +++ b/compiler/hieFile/HieBin.hs @@ -117,7 +117,7 @@ writeHieFile hie_file_path hiefile = do symtab_p_p <- tellBin bh0 put_ bh0 symtab_p_p - -- Make some intial state + -- Make some initial state symtab_next <- newFastMutInt writeFastMutInt symtab_next 0 symtab_map <- newIORef emptyUFM diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 37355a1329..db3157f39b 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -885,7 +885,7 @@ ppr_ty ctxt_prec (IfaceCoercionTy co) ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ RuntimeRep variables are considered by many (most?) users to be little more than syntactic noise. When the notion was introduced there was a -signficant and understandable push-back from those with pedagogy in +significant and understandable push-back from those with pedagogy in mind, which argued that RuntimeRep variables would throw a wrench into nearly any teach approach since they appear in even the lowly ($) function's type, diff --git a/compiler/iface/LoadIface.hs b/compiler/iface/LoadIface.hs index 2485f07df2..38f7524b8e 100644 --- a/compiler/iface/LoadIface.hs +++ b/compiler/iface/LoadIface.hs @@ -549,7 +549,7 @@ But there is a HORRIBLE HACK here. * And that means we end up loading M.hi-boot, because those data types are not yet in the type environment. -But in this wierd case, /all/ we need is the types. We don't need +But in this weird case, /all/ we need is the types. We don't need instances, rules etc. And if we put the instances in the EPS we get "duplicate instance" warnings when we compile the "real" instance in M itself. Hence the strange business of just updateing diff --git a/compiler/main/ErrUtils.hs b/compiler/main/ErrUtils.hs index f0fa1441f9..c66496bc61 100644 --- a/compiler/main/ErrUtils.hs +++ b/compiler/main/ErrUtils.hs @@ -879,7 +879,7 @@ the whole thing with 'withTiming'. Instead we wrap the processing of each individual stream element, all along the codegen pipeline, using the appropriate label for the pass to which this processing belongs. That generates a lot more data but allows us to get fine-grained timings about all the passes and we can -easily compute totals withh tools like ghc-events-analyze (see below). +easily compute totals with tools like ghc-events-analyze (see below). Producing an eventlog for GHC diff --git a/compiler/main/GhcMake.hs b/compiler/main/GhcMake.hs index 6599da07f4..93bdb85f19 100644 --- a/compiler/main/GhcMake.hs +++ b/compiler/main/GhcMake.hs @@ -730,7 +730,7 @@ findPartiallyCompletedCycles modsDone theGraph -- -- | Unloading unload :: HscEnv -> [Linkable] -> IO () -unload hsc_env stable_linkables -- Unload everthing *except* 'stable_linkables' +unload hsc_env stable_linkables -- Unload everything *except* 'stable_linkables' = case ghcLink (hsc_dflags hsc_env) of LinkInMemory -> Linker.unload hsc_env stable_linkables _other -> return () diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index baed7f5ec1..b3ee7f5e6c 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -2135,7 +2135,7 @@ isDllName dflags this_mod name -- On Windows the hack for #8696 makes it unlinkable. -- As the entire setup of the code from Cmm down to the RTS expects -- the use of trampolines for the imported functions only when - -- doing intra-package linking, e.g. refering to a symbol defined in the same + -- doing intra-package linking, e.g. referring to a symbol defined in the same -- package should not use a trampoline. -- I much rather have dynamic TH not supported than the entire Dynamic linking -- not due to a hack. diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index ae491ac02d..f087d96bca 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -1280,7 +1280,7 @@ So we have to *predict* the result here, which is revolting. In particular CorePrep expands Integer and Natural literals. So in the prediction code here we resort to applying the same expansion (cvt_literal). -There are also numberous other ways in which we can introduce inconsistencies +There are also numerous other ways in which we can introduce inconsistencies between CorePrep and TidyPgm. See Note [CAFfyness inconsistencies due to eta expansion in TidyPgm] for one such example. diff --git a/compiler/main/ToolSettings.hs b/compiler/main/ToolSettings.hs index 952e5869fc..82d125b5f6 100644 --- a/compiler/main/ToolSettings.hs +++ b/compiler/main/ToolSettings.hs @@ -9,7 +9,7 @@ import Fingerprint -- | Settings for other executables GHC calls. -- --- Probably should futher split down by phase, or split between +-- Probably should further split down by phase, or split between -- platform-specific and platform-agnostic. data ToolSettings = ToolSettings { toolSettings_ldSupportsCompactUnwind :: Bool diff --git a/compiler/nativeGen/BlockLayout.hs b/compiler/nativeGen/BlockLayout.hs index d8b844c32b..45779d8089 100644 --- a/compiler/nativeGen/BlockLayout.hs +++ b/compiler/nativeGen/BlockLayout.hs @@ -79,7 +79,7 @@ import Control.Monad (foldM) Edge weights not only represent likelyhood of control transfer between blocks but also how much a block would benefit from being placed sequentially after it's predecessor. - For example blocks which are preceeded by an info table are more likely to end + For example blocks which are preceded by an info table are more likely to end up in a different cache line than their predecessor and we can't eliminate the jump so there is less benefit to placing them sequentially. diff --git a/compiler/nativeGen/Format.hs b/compiler/nativeGen/Format.hs index 31472893e7..745d1e7b65 100644 --- a/compiler/nativeGen/Format.hs +++ b/compiler/nativeGen/Format.hs @@ -3,7 +3,7 @@ -- -- TODO: Signed vs unsigned? -- --- TODO: This module is currenly shared by all architectures because +-- TODO: This module is currently shared by all architectures because -- NCGMonad need to know about it to make a VReg. It would be better -- to have architecture specific formats, and do the overloading -- properly. eg SPARC doesn't care about FF80. diff --git a/compiler/nativeGen/PIC.hs b/compiler/nativeGen/PIC.hs index 7ea68e1105..a38f3fa18f 100644 --- a/compiler/nativeGen/PIC.hs +++ b/compiler/nativeGen/PIC.hs @@ -420,7 +420,7 @@ picRelative dflags arch OSDarwin lbl -- On AIX we use an indirect local TOC anchored by 'gotLabel'. -- This way we use up only one global TOC entry per compilation-unit --- (this is quite similiar to GCC's @-mminimal-toc@ compilation mode) +-- (this is quite similar to GCC's @-mminimal-toc@ compilation mode) picRelative dflags _ OSAIX lbl = CmmLabelDiffOff lbl gotLabel 0 (wordWidth dflags) @@ -623,7 +623,7 @@ pprImportedSymbol _ (Platform { platformMini = PlatformMini { platformMini_os = -- XCOFF / AIX -- --- Similiar to PPC64 ELF v1, there's dedicated TOC register (r2). To +-- Similar to PPC64 ELF v1, there's dedicated TOC register (r2). To -- workaround the limitation of a global TOC we use an indirect TOC -- with the label `ghc_toc_table`. -- diff --git a/compiler/nativeGen/PPC/CodeGen.hs b/compiler/nativeGen/PPC/CodeGen.hs index 5f852973ae..ea663dcc23 100644 --- a/compiler/nativeGen/PPC/CodeGen.hs +++ b/compiler/nativeGen/PPC/CodeGen.hs @@ -1690,7 +1690,7 @@ genCCall' dflags gcp target dest_regs args `appOL` codeAfter) GCPAIX -> return ( dynCode -- AIX/XCOFF follows the PowerOPEN ABI - -- which is quite similiar to LinuxPPC64/ELFv1 + -- which is quite similar to LinuxPPC64/ELFv1 `appOL` codeBefore `snocOL` ST spFormat toc (AddrRegImm sp (ImmInt 20)) `snocOL` LD II32 r11 (AddrRegImm dynReg (ImmInt 0)) diff --git a/compiler/nativeGen/RegAlloc/Graph/Spill.hs b/compiler/nativeGen/RegAlloc/Graph/Spill.hs index eccc83eb48..22a88c02c0 100644 --- a/compiler/nativeGen/RegAlloc/Graph/Spill.hs +++ b/compiler/nativeGen/RegAlloc/Graph/Spill.hs @@ -297,7 +297,7 @@ patchInstr patchInstr reg instr = do nUnique <- newUnique - -- The register we're rewriting is suppoed to be virtual. + -- The register we're rewriting is supposed to be virtual. -- If it's not then something has gone horribly wrong. let nReg = case reg of diff --git a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs index 52f590948a..4be25a71ba 100644 --- a/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs +++ b/compiler/nativeGen/RegAlloc/Graph/SpillCost.hs @@ -297,7 +297,7 @@ nodeDegree classOfVirtualReg graph reg -- | Show a spill cost record, including the degree from the graph --- and final calulated spill cost. +-- and final calculated spill cost. pprSpillCostRecord :: (VirtualReg -> RegClass) -> (Reg -> SDoc) diff --git a/compiler/nativeGen/RegClass.hs b/compiler/nativeGen/RegClass.hs index fbbb786817..f4170cca94 100644 --- a/compiler/nativeGen/RegClass.hs +++ b/compiler/nativeGen/RegClass.hs @@ -12,7 +12,7 @@ import Unique -- | The class of a register. -- Used in the register allocator. --- We treat all registers in a class as being interchangable. +-- We treat all registers in a class as being interchangeable. -- data RegClass = RcInteger diff --git a/compiler/nativeGen/SPARC/CodeGen/Expand.hs b/compiler/nativeGen/SPARC/CodeGen/Expand.hs index a29c24dcd4..237311956e 100644 --- a/compiler/nativeGen/SPARC/CodeGen/Expand.hs +++ b/compiler/nativeGen/SPARC/CodeGen/Expand.hs @@ -51,7 +51,7 @@ expandBlockInstrs (ii:is) -- | In the SPARC instruction set the FP register pairs that are used --- to hold 64 bit floats are refered to by just the first reg +-- to hold 64 bit floats are referred to by just the first reg -- of the pair. Remap our internal reg pairs to the appropriate reg. -- -- For example: diff --git a/compiler/nativeGen/X86/Instr.hs b/compiler/nativeGen/X86/Instr.hs index 7e47860143..80a2c8b28e 100644 --- a/compiler/nativeGen/X86/Instr.hs +++ b/compiler/nativeGen/X86/Instr.hs @@ -816,7 +816,7 @@ x86_mkJumpInstr id -- | | -- +-------------------+ -- --- In essense each allocation larger than a page size needs to be chunked and +-- In essence each allocation larger than a page size needs to be chunked and -- a probe emitted after each page allocation. You have to hit the guard -- page so the kernel can map in the next page, otherwise you'll segfault. -- diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y index 8ee4053d08..b91e1681c5 100644 --- a/compiler/parser/Parser.y +++ b/compiler/parser/Parser.y @@ -2247,7 +2247,7 @@ with constructor names (see Note [Parsing data constructors is hard]). Due to simplified syntax, GADT constructor names (left-hand side of '::') use simpler grammar production than usual data constructor names. As a -consequence, GADT constructor names are resticted (names like '(*)' are +consequence, GADT constructor names are restricted (names like '(*)' are allowed in usual data constructors, but not in GADTs). -} diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs index 9cccc7d1c0..89634193e4 100644 --- a/compiler/parser/RdrHsSyn.hs +++ b/compiler/parser/RdrHsSyn.hs @@ -564,7 +564,7 @@ declarations and types as a reversed list of TyEl: | TyElOpd (HsType GhcPs) | ... -For example, both occurences of (C ! D) in the following example are parsed +For example, both occurrences of (C ! D) in the following example are parsed into equal lists of TyEl: data T = C ! D => C ! D results in [ TyElOpd (HsTyVar "D") @@ -2878,7 +2878,7 @@ failOpNotEnabledImportQualifiedPost loc = addError loc msg failOpImportQualifiedTwice :: SrcSpan -> P () failOpImportQualifiedTwice loc = addError loc msg where - msg = text "Multiple occurences of 'qualified'" + msg = text "Multiple occurrences of 'qualified'" warnStarIsType :: SrcSpan -> P () warnStarIsType span = addWarning Opt_WarnStarIsType span msg diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs index a61c163c32..72d99a5b8e 100644 --- a/compiler/prelude/PrelRules.hs +++ b/compiler/prelude/PrelRules.hs @@ -734,7 +734,7 @@ There are two cases: and match_Integer_shift_op. Here we could in principle shift by any amount, but we arbitary - limit the shift to 4 bits; in particualr we do not want shift by a + limit the shift to 4 bits; in particular we do not want shift by a huge amount, which can happen in code like that above. The two cases are more different in their code paths that is comfortable, diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index f47880b58d..076854b4d2 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2057,7 +2057,7 @@ primop FetchAddByteArrayOp_Int "fetchAddIntArray#" GenPrimOp primop FetchSubByteArrayOp_Int "fetchSubIntArray#" GenPrimOp MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) {Given an array, and offset in machine words, and a value to subtract, - atomically substract the value to the element. Returns the value of + atomically subtract the value to the element. Returns the value of the element before the operation. Implies a full memory barrier.} with has_side_effects = True can_fail = True diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs index 586548f5d8..00a76df77a 100644 --- a/compiler/rename/RnEnv.hs +++ b/compiler/rename/RnEnv.hs @@ -1137,7 +1137,7 @@ constructor namespace before looking in the data constructor namespace to deal with `DataKinds`. There is however, as always, one exception to this scheme. If we find -an ambiguous occurence of a record selector and DuplicateRecordFields +an ambiguous occurrence of a record selector and DuplicateRecordFields is enabled then we defer the selection until the typechecker. -} diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 791b6a4ceb..966e027fe2 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -686,7 +686,7 @@ rnFamInstEqn doc atfi rhs_kvars ; tycon' <- lookupFamInstName mb_cls tycon ; let pat_kity_vars_with_dups = extractHsTyArgRdrKiTyVarsDup pats -- Use the "...Dups" form because it's needed - -- below to report unsed binder on the LHS + -- below to report unused binder on the LHS -- Implicitly bound variables, empty if we have an explicit 'forall' according -- to the "forall-or-nothing" rule. diff --git a/compiler/rename/RnTypes.hs b/compiler/rename/RnTypes.hs index 434ed496f1..1e7d101089 100644 --- a/compiler/rename/RnTypes.hs +++ b/compiler/rename/RnTypes.hs @@ -1653,7 +1653,7 @@ extractHsTysRdrTyVarsDups :: [LHsType GhcPs] -> FreeKiTyVarsWithDups extractHsTysRdrTyVarsDups tys = extract_ltys tys [] --- Returns the free kind variables of any explictly-kinded binders, returning +-- Returns the free kind variables of any explicitly-kinded binders, returning -- variable occurrences in left-to-right order. -- See Note [Ordering of implicit variables]. -- NB: Does /not/ delete the binders themselves. @@ -1758,7 +1758,7 @@ extract_hs_tv_bndrs tv_bndrs acc_vars body_vars tv_bndr_rdrs = map hsLTyVarLocName tv_bndrs extract_hs_tv_bndrs_kvs :: [LHsTyVarBndr GhcPs] -> [Located RdrName] --- Returns the free kind variables of any explictly-kinded binders, returning +-- Returns the free kind variables of any explicitly-kinded binders, returning -- variable occurrences in left-to-right order. -- See Note [Ordering of implicit variables]. -- NB: Does /not/ delete the binders themselves. diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs index 35862aeabe..2bb69fa6f9 100644 --- a/compiler/simplCore/CSE.hs +++ b/compiler/simplCore/CSE.hs @@ -256,7 +256,7 @@ We do not want to extend the substitution with (y -> x |> co); since y is of unlifted type, this would destroy the let/app invariant if (x |> co) was not ok-for-speculation. -But surely (x |> co) is ok-for-speculation, becasue it's a trivial +But surely (x |> co) is ok-for-speculation, because it's a trivial expression, and x's type is also unlifted, presumably. Well, maybe not if you are using unsafe casts. I actually found a case where we had diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index bd5b3a3055..75c55c698c 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -162,7 +162,7 @@ The interesting cases of the analysis: Return: C(e₁) ∪ (fv e₁) × {x} ∪ {(x,x)} * Let v = rhs in body: In addition to the results from the subexpressions, add all co-calls from - everything that the body calls together with v to everthing that is called + everything that the body calls together with v to everything that is called by v. Return: C'(rhs) ∪ C(body) ∪ (fv rhs) × {v'| {v,v'} ∈ C(body)} * Letrec v₁ = rhs₁ ... vₙ = rhsₙ in body @@ -318,7 +318,7 @@ Note [Taking boring variables into account] If we decide that the variable bound in `let x = e1 in e2` is not interesting, the analysis of `e2` will not report anything about `x`. To ensure that `callArityBind` does still do the right thing we have to take that into account -everytime we would be lookup up `x` in the analysis result of `e2`. +every time we would be lookup up `x` in the analysis result of `e2`. * Instead of calling lookupCallArityRes, we return (0, True), indicating that this variable might be called many times with no arguments. * Instead of checking `calledWith x`, we assume that everything can be called diff --git a/compiler/simplCore/Exitify.hs b/compiler/simplCore/Exitify.hs index f5a4138566..1183e6cf02 100644 --- a/compiler/simplCore/Exitify.hs +++ b/compiler/simplCore/Exitify.hs @@ -431,7 +431,7 @@ To prevent this, we need to recognize exit join points, and then disable inlining. Exit join points, recognizeable using `isExitJoinId` are join points with an -occurence in a recursive group, and can be recognized (after the occurence +occurrence in a recursive group, and can be recognized (after the occurrence analyzer ran!) using `isExitJoinId`. This function detects joinpoints with `occ_in_lam (idOccinfo id) == True`, because the lambdas of a non-recursive join point are not considered for @@ -493,7 +493,7 @@ free variables of the join point. We do not just `filter (`elemVarSet` fvs) captured`, as there might be shadowing, and `captured` may contain multiple variables with the same Unique. I -these cases we want to abstract only over the last occurence, hence the `foldr` +these cases we want to abstract only over the last occurrence, hence the `foldr` (with emphasis on the `r`). This is #15110. -} diff --git a/compiler/simplCore/OccurAnal.hs b/compiler/simplCore/OccurAnal.hs index d10b1eda22..500dc7a912 100644 --- a/compiler/simplCore/OccurAnal.hs +++ b/compiler/simplCore/OccurAnal.hs @@ -371,7 +371,7 @@ That's why we compute So we must *not* postInlineUnconditionally 'g', even though its RHS turns out to be trivial. (I'm assuming that 'g' is - not choosen as a loop breaker.) Why not? Because then we + not chosen as a loop breaker.) Why not? Because then we drop the binding for 'g', which leaves it out of scope in the RULE! @@ -1790,7 +1790,7 @@ occAnal env (Case scrut bndr ty alts) | t `tickishScopesLike` SoftScope -- No reason to not look through all ticks here, but only -- for soft-scoped ticks we can do so without having to - -- update returned occurance info (see occAnal) + -- update returned occurrence info (see occAnal) = second (Tick t) $ occ_anal_scrut e alts occ_anal_scrut scrut _alts @@ -2210,7 +2210,7 @@ extendFvs env s Note [Binder swap] ~~~~~~~~~~~~~~~~~~ -The "binder swap" tranformation swaps occurence of the +The "binder swap" tranformation swaps occurrence of the scrutinee of a case for occurrences of the case-binder: (1) case x of b { pi -> ri } @@ -2325,7 +2325,7 @@ as Dead, so we must zap the OccInfo on cb before making the binding x = cb. See #5028. NB: the OccInfo on /occurrences/ really doesn't matter much; the simplifier -doesn't use it. So this is only to satisfy the perhpas-over-picky Lint. +doesn't use it. So this is only to satisfy the perhaps-over-picky Lint. Historical note [no-case-of-case] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2535,7 +2535,7 @@ zapDetails = markAllMany . markAllNonTailCalled -- effectively sets to noOccInfo lookupDetails :: UsageDetails -> Id -> OccInfo lookupDetails ud id - | isCoVar id -- We do not currenly gather occurrence info (from types) + | isCoVar id -- We do not currently gather occurrence info (from types) = noOccInfo -- for CoVars, so we must conservatively mark them as used -- See Note [DoO not mark CoVars as dead] | otherwise diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 569bcfd3dc..c4f179ba55 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -1623,7 +1623,7 @@ wrapJoinCont env cont thing_inside = thing_inside env cont | not (sm_case_case (getMode env)) - -- See Note [Join points wih -fno-case-of-case] + -- See Note [Join points with -fno-case-of-case] = do { (floats1, expr1) <- thing_inside env (mkBoringStop (contHoleType cont)) ; let (floats2, expr2) = wrapJoinFloatsX floats1 expr1 ; (floats3, expr3) <- rebuild (env `setInScopeFromF` floats2) expr2 cont @@ -1691,7 +1691,7 @@ We need do make the continuation E duplicable (since we are duplicating it) with mkDuableCont. -Note [Join points wih -fno-case-of-case] +Note [Join points with -fno-case-of-case] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Supose case-of-case is switched off, and we are simplifying @@ -2965,7 +2965,7 @@ knownCon env scrut dc_floats dc dc_ty_args dc_args bndr bs rhs cont | exprIsTrivial scrut = return (emptyFloats env , extendIdSubst env bndr (DoneEx scrut Nothing)) | otherwise = do { dc_args <- mapM (simplVar env) bs - -- dc_ty_args are aready OutTypes, + -- dc_ty_args are already OutTypes, -- but bs are InBndrs ; let con_app = Var (dataConWorkId dc) `mkTyApps` dc_ty_args diff --git a/compiler/simplStg/RepType.hs b/compiler/simplStg/RepType.hs index 75fde79d87..e6eb907f19 100644 --- a/compiler/simplStg/RepType.hs +++ b/compiler/simplStg/RepType.hs @@ -330,7 +330,7 @@ Examples include: The "representation or a primitive entity" specifies what kind of register is needed and how many bits are required. The data type TyCon.PrimRep -enumerates all the possiblities. +enumerates all the possibilities. data PrimRep = VoidRep diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 213064d599..36c613c186 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -881,7 +881,7 @@ To do the injectivity check: 1. We build VarUsages that represent the LHS (rather, the portion of the LHS that is flagged as injective); each usage on the LHS is NotPresent, because we -hvae not yet looked at the RHS. +have not yet looked at the RHS. 2. We also build a VarUsage for the RHS, done by injTyVarUsages. diff --git a/compiler/typecheck/TcBinds.hs b/compiler/typecheck/TcBinds.hs index b51b0041e3..d45ed2ea8c 100644 --- a/compiler/typecheck/TcBinds.hs +++ b/compiler/typecheck/TcBinds.hs @@ -1098,7 +1098,7 @@ checkOverloadedSig monomorphism_restriction_applies sig {- Note [Partial type signatures and generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If /any/ of the signatures in the gropu is a partial type signature +If /any/ of the signatures in the group is a partial type signature f :: _ -> Int then we *always* use the InferGen plan, and hence tcPolyInfer. We do this even for a local binding with -XMonoLocalBinds, when diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs index 20790200d0..9d2acfc9f7 100644 --- a/compiler/typecheck/TcCanonical.hs +++ b/compiler/typecheck/TcCanonical.hs @@ -609,7 +609,7 @@ makeSuperClasses, giving us a a second quantified constrait (forall a. a ~# b) BUT this is an unboxed value! And nothing has prepared us for dictionary "functions" that are unboxed. Actually it does just -about work, but the simplier ends up with stuff like +about work, but the simplifier ends up with stuff like case (/\a. eq_sel d) of df -> ...(df @Int)... and fails to simplify that any further. And it doesn't satisfy isPredTy any more. diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 3a7369e2f9..3f89e2c033 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1016,7 +1016,7 @@ a poly-kinded typeclass for a poly-kinded datatype. For example: class Category (cat :: k -> k -> *) where newtype T (c :: k -> k -> *) a b = MkT (c a b) deriving Category -This case is suprisingly tricky. To see why, let's write out what instance GHC +This case is surprisingly tricky. To see why, let's write out what instance GHC will attempt to derive (using -fprint-explicit-kinds syntax): instance Category k1 (T k2 c) where ... @@ -1289,7 +1289,7 @@ When there are no type families, it's quite easy: instance Eq [a] => Eq (S a) -- by coercion sym (Eq (:CoS a)) : Eq [a] ~ Eq (S a) instance Monad [] => Monad S -- by coercion sym (Monad :CoS) : Monad [] ~ Monad S -When type familes are involved it's trickier: +When type families are involved it's trickier: data family T a b newtype instance T Int a = MkT [a] deriving( Eq, Monad ) diff --git a/compiler/typecheck/TcDerivInfer.hs b/compiler/typecheck/TcDerivInfer.hs index 97dffcd1cf..10c58d502e 100644 --- a/compiler/typecheck/TcDerivInfer.hs +++ b/compiler/typecheck/TcDerivInfer.hs @@ -991,7 +991,7 @@ more complicated it will be reported in a civilised way. Note [Error reporting for deriving clauses] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -A suprisingly tricky aspect of deriving to get right is reporting sensible +A surprisingly tricky aspect of deriving to get right is reporting sensible error messages. In particular, if simplifyDeriv reaches a constraint that it cannot solve, which might include: diff --git a/compiler/typecheck/TcHoleErrors.hs b/compiler/typecheck/TcHoleErrors.hs index a2eee57947..0e8f0a6d06 100644 --- a/compiler/typecheck/TcHoleErrors.hs +++ b/compiler/typecheck/TcHoleErrors.hs @@ -980,7 +980,7 @@ tcCheckHoleFit (TyH {..}) hole_ty ty = discardErrs $ ; traceTc "w_givens are: " $ ppr w_givens ; rem <- runTcSDeriveds $ simpl_top w_givens -- We don't want any insoluble or simple constraints left, but - -- solved implications are ok (and neccessary for e.g. undefined) + -- solved implications are ok (and necessary for e.g. undefined) ; traceTc "rems was:" $ ppr rem ; traceTc "}" empty ; return (isSolvedWC rem, wrp) } } diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index e8b67bbc89..2f5382d581 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -265,7 +265,7 @@ There are three possibilities: So we default it to 'Any' of the right kind. All this works for both type and kind variables (indeed - the two are the same thign). + the two are the same thing). * SkolemiseFlexi: is a special case for the LHS of RULES. See Note [Zonking the LHS of a RULE] diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 4ed472386c..5f96134676 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1323,7 +1323,7 @@ saturateFamApp :: TcType -> TcKind -> TcM (TcType, TcKind) -- Precondition for (saturateFamApp ty kind): -- tcTypeKind ty = kind -- --- If 'ty' is an unsaturated family application wtih trailing +-- If 'ty' is an unsaturated family application with trailing -- invisible arguments, instanttiate them. -- See Note [saturateFamApp] @@ -1559,7 +1559,7 @@ very convenient to typecheck instance types like any other HsSigType. Admittedly the '(Eq a => Eq [a]) => blah' case is erroneous, but it's better to reject in checkValidType. If we say that the body kind should be '*' we risk getting TWO error messages, one saying that Eq -[a] doens't have kind '*', and one saying that we need a Constraint to +[a] doesn't have kind '*', and one saying that we need a Constraint to the left of the outer (=>). How do we figure out the right body kind? Well, it's a bit of a diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 6b69928419..a2aa82e51b 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -604,7 +604,7 @@ we keep? More subtle than you might think! and can be reported as redundant. See Note [Tracking redundant constraints] in TcSimplify. - It transpires that using the outermost one is reponsible for an + It transpires that using the outermost one is responsible for an 8% performance improvement in nofib cryptarithm2, compared to just rolling the dice. I didn't investigate why. @@ -1582,7 +1582,7 @@ inertsCanDischarge inerts tv rhs fr keep_deriv ev_i | Wanted WOnly <- ctEvFlavour ev_i -- inert is [W] , (Wanted WDeriv, _) <- fr -- work item is [WD] - = True -- Keep a derived verison of the work item + = True -- Keep a derived version of the work item | otherwise = False -- Work item is fully discharged diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 746b48401b..afc807c461 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -153,7 +153,7 @@ tcInferPatSynDecl (PSB { psb_id = lname@(dL->L _ name), psb_args = details mk_named_tau arg = (getName arg, mkSpecForAllTys ex_tvs (varType arg)) -- The mkSpecForAllTys is important (#14552), albeit - -- slightly artifical (there is no variable with this funny type). + -- slightly artificial (there is no variable with this funny type). -- We do not want to quantify over variable (alpha::k) -- that mention the existentially-bound type variables -- ex_tvs in its kind k. @@ -307,7 +307,7 @@ and is not implicitly instantiated. So in mkProvEvidence we lift (a ~# b) to (a ~ b). Tiresome, and marginally less efficient, if the builder/martcher are not inlined. -See also Note [Lift equality constaints when quantifying] in TcType +See also Note [Lift equality constraints when quantifying] in TcType Note [Coercions that escape] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 59f9b45617..eb940aa1ee 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -474,7 +474,7 @@ creating a new EvVar when we have a new goal that we have solved in the past. But in particular, we can use it to create *recursive* dictionaries. -The simplest, degnerate case is +The simplest, degenerate case is instance C [a] => C [a] where ... If we have [W] d1 :: C [x] @@ -2859,7 +2859,7 @@ implications. Consider a ~ F b, forall c. b~Int => blah If we have F b ~ fsk in the flat-cache, and we push that into the nested implication, we might miss that F b can be rewritten to F Int, -and hence perhpas solve it. Moreover, the fsk from outside is +and hence perhaps solve it. Moreover, the fsk from outside is flattened out after solving the outer level, but and we don't do that flattening recursively. -} @@ -2881,7 +2881,7 @@ nestTcS (TcS thing_inside) ; new_inerts <- TcM.readTcRef new_inert_var - -- we want to propogate the safe haskell failures + -- we want to propagate the safe haskell failures ; let old_ic = inert_cans inerts new_ic = inert_cans new_inerts nxt_ic = old_ic { inert_safehask = inert_safehask new_ic } @@ -2978,7 +2978,7 @@ Consider forall b. empty => Eq [a] We solve the simple (Eq [a]), under nestTcS, and then turn our attention to the implications. It's definitely fine to use the solved dictionaries on -the inner implications, and it can make a signficant performance difference +the inner implications, and it can make a significant performance difference if you do so. -} diff --git a/compiler/typecheck/TcSigs.hs b/compiler/typecheck/TcSigs.hs index b4ef967fcb..1e284ec0a7 100644 --- a/compiler/typecheck/TcSigs.hs +++ b/compiler/typecheck/TcSigs.hs @@ -123,7 +123,7 @@ for two reasons: may actually give rise to f :: forall k. forall (f::k -> *) (a:k). f a -> f a So the sig_tvs will be [k,f,a], but only f,a are scoped. - NB: the scoped ones are not necessarily the *inital* ones! + NB: the scoped ones are not necessarily the *initial* ones! * Even aside from kind polymorphism, there may be more instantiated type variables than lexically-scoped ones. For example: diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 9a81e35e06..18565405f1 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -454,9 +454,9 @@ We do the following steps: B :-> TcTyCon <initial kind> (thereby overriding the B :-> TyConPE binding) and do kcLTyClDecl on each decl to get equality constraints on - all those inital kinds + all those initial kinds - - Generalise the inital kind, making a poly-kinded TcTyCon + - Generalise the initial kind, making a poly-kinded TcTyCon 3. Back in tcTyDecls, extend the envt with bindings of the poly-kinded TcTyCons, again overriding the promotion-error bindings. @@ -1692,7 +1692,7 @@ There's also a change in the renamer: inside the data constructor to determine the result kind. See Note [Unlifted Newtypes and CUSKs] for more detail. -For completeness, it was also neccessary to make coerce work on +For completeness, it was also necessary to make coerce work on unlifted types, resolving #13595. -} diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 1537859d1b..90680f093f 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -277,7 +277,7 @@ Note, though, that a /bound/ type variable can (and probably should) be a TyVar. E.g forall a. a -> a Here 'a' is really just a deBruijn-number; it certainly does not have -a signficant TcLevel (as every TcTyVar does). So a forall-bound type +a significant TcLevel (as every TcTyVar does). So a forall-bound type variable should be TyVars; and hence a TyVar can appear free in a TcType. The type checker and constraint solver can also encounter /free/ type @@ -1657,7 +1657,7 @@ pickQuantifiablePreds qtvs theta EqPred eq_rel ty1 ty2 | quantify_equality eq_rel ty1 ty2 , Just (cls, tys) <- boxEqPred eq_rel ty1 ty2 - -- boxEqPred: See Note [Lift equality constaints when quantifying] + -- boxEqPred: See Note [Lift equality constraints when quantifying] , pick_cls_pred flex_ctxt cls tys -> Just (mkClassPred cls tys) @@ -1875,7 +1875,7 @@ Notice that See also TcTyDecls.checkClassCycles. -Note [Lift equality constaints when quantifying] +Note [Lift equality constraints when quantifying] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We can't quantify over a constraint (t1 ~# t2) because that isn't a predicate type; see Note [Types for coercions, predicates, and evidence] diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index f02cb887cf..3f780fe546 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -2574,7 +2574,7 @@ Notice that: positions where the class header has no influence over the parameter. Hence the fancy footwork in pp_expected_ty - - Although the binders in the axiom are aready tidy, we must + - Although the binders in the axiom are already tidy, we must re-tidy them to get a fresh variable name when we shadow - The (ax_tvs \\ inst_tvs) is to avoid tidying one of the diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs index b99983f779..47868ad9a1 100644 --- a/compiler/types/Coercion.hs +++ b/compiler/types/Coercion.hs @@ -2856,7 +2856,7 @@ simplifyArgsWorker orig_ki_binders orig_inner_ki orig_fvs "simplifyArgsWorker wandered into deeper water than usual" -- This debug information is commented out because leaving it in -- causes a ~2% increase in allocations in T9872d. - -- That's independent of the analagous case in flatten_args_fast + -- That's independent of the analogous case in flatten_args_fast -- in TcFlatten: -- each of these causes a 2% increase on its own, so commenting them -- both out gives a 4% decrease in T9872d. diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index c0b6414f8c..b491948cd9 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -1253,7 +1253,7 @@ because type families are saturated. But if S has a type family on its RHS we expand /before/ normalising the args t1, t2. If we normalise t1, t2 first, we'll re-normalise them -after expansion, and that can lead to /exponential/ behavour; see #13035. +after expansion, and that can lead to /exponential/ behaviour; see #13035. Notice, though, that expanding first can in principle duplicate t1,t2, which might contain redexes. I'm sure you could conjure up an exponential diff --git a/compiler/types/TyCoFVs.hs b/compiler/types/TyCoFVs.hs index 19371df254..eefd68f145 100644 --- a/compiler/types/TyCoFVs.hs +++ b/compiler/types/TyCoFVs.hs @@ -70,7 +70,7 @@ so we profiled several versions, exploring different implementation strategies. tyCoVarsOfType ty = fvVarSet $ tyCoFVsOfType ty This is not nice, because FV introduces some overhead to implement - determinism, and throught its "interesting var" function, neither of which + determinism, and through its "interesting var" function, neither of which we need here, so they are a complete waste. 2. UnionVarSet version: instead of reusing the FV-based code, we simply used diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index b1337a1e14..94a09288b5 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -693,7 +693,7 @@ The new scheme also does not depend in any way on architecture specific details. We still use this scheme even with LEB128 available, -as it has less overhead for truely large numbers. (> maxBound :: Int64) +as it has less overhead for truly large numbers. (> maxBound :: Int64) The instance is used for in Binary Integer and Binary Rational in basicTypes/Literal.hs -} diff --git a/compiler/utils/GraphOps.hs b/compiler/utils/GraphOps.hs index bb4504ff1f..0a7981b0c8 100644 --- a/compiler/utils/GraphOps.hs +++ b/compiler/utils/GraphOps.hs @@ -264,8 +264,8 @@ delCoalesce k1 k2 -- | Add a color preference to the graph, creating nodes if required. --- The most recently added preference is the most prefered. --- The algorithm tries to assign a node it's prefered color if possible. +-- The most recently added preference is the most preferred. +-- The algorithm tries to assign a node it's preferred color if possible. -- addPreference :: Uniquable k diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index cd3e2a5f5b..bbc365b774 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -1239,7 +1239,7 @@ warnPprTrace True file line msg x where heading = hsep [text "WARNING: file", text file <> comma, text "line", int line] --- | Panic with an assertation failure, recording the given file and +-- | Panic with an assertion failure, recording the given file and -- line number. Should typically be accessed with the ASSERT family of macros assertPprPanic :: HasCallStack => String -> Int -> SDoc -> a assertPprPanic _file _line msg diff --git a/compiler/utils/UniqDFM.hs b/compiler/utils/UniqDFM.hs index 1b104a66cd..f9588e9b0b 100644 --- a/compiler/utils/UniqDFM.hs +++ b/compiler/utils/UniqDFM.hs @@ -397,7 +397,7 @@ instance Monoid (UniqDFM a) where mempty = emptyUDFM mappend = (Semi.<>) --- This should not be used in commited code, provided for convenience to +-- This should not be used in committed code, provided for convenience to -- make ad-hoc conversions when developing alwaysUnsafeUfmToUdfm :: UniqFM elt -> UniqDFM elt alwaysUnsafeUfmToUdfm = listToUDFM_Directly . nonDetUFMToList diff --git a/docs/coding-style.html b/docs/coding-style.html index dbf0f8729a..c94913eac8 100644 --- a/docs/coding-style.html +++ b/docs/coding-style.html @@ -332,7 +332,7 @@ can be "polymorphic" as these examples show: Inline functions should be "static inline" because: <ul> <li> -gcc will delete static inlines if not used or theyre always inlined. +gcc will delete static inlines if not used or they're always inlined. <li> if they're externed, we could get conflicts between 2 copies of the diff --git a/docs/opt-coercion/fc-normalization-rta.tex b/docs/opt-coercion/fc-normalization-rta.tex index a1e7d4201d..c3bf41bd81 100755 --- a/docs/opt-coercion/fc-normalization-rta.tex +++ b/docs/opt-coercion/fc-normalization-rta.tex @@ -802,7 +802,7 @@ $$ \gamma ; \sym{\gamma} & \rsa{} & \refl{\tau} & \text{if}\,\gamma : \tau \psim \phi \end{array} $$ -But ther are much more complicated rewrites to consider. +But there are much more complicated rewrites to consider. Consider these coercions, where $C_N$ is the axiom generated by the newtype coercion in Section~\ref{sec:newtype}: $$ diff --git a/docs/rts/rts.tex b/docs/rts/rts.tex index bd54824707..d5d4f6d67d 100644 --- a/docs/rts/rts.tex +++ b/docs/rts/rts.tex @@ -640,7 +640,7 @@ only requires one argument so it leaves the second argument as a until @f@ calls @g@ which requires two arguments: the argument passed to it by @f@ and the pending argument which was passed to @f@. -Unboxed pending arguments are always preceeded by a ``tag'' which says +Unboxed pending arguments are always preceded by a ``tag'' which says how large the argument is. This allows the garbage collector to locate pointers within the stack. @@ -3250,7 +3250,7 @@ entered a @AP@ by switching worlds, entering the @AP@, pushing the arguments and function onto the stack, and entering the function which, likely as not, will be a byte-code object which we will enter by \emph{returning} to the byte-code interpreter. To avoid such -gratuitious world switching, we choose to recognise certain closure +gratuitous world switching, we choose to recognise certain closure types as being ``standard'' --- and duplicate the entry code for the ``standard closures'' in the bytecode interpreter. diff --git a/docs/users_guide/ghci.rst b/docs/users_guide/ghci.rst index e5e5c37402..35a49766b4 100644 --- a/docs/users_guide/ghci.rst +++ b/docs/users_guide/ghci.rst @@ -2387,7 +2387,7 @@ commonly used commands. Attempting to redefine an existing command name results in an error unless the ``:def!`` form is used, in which case the old command with that name is silently overwritten. However for builtin commands - the old command can still be used by preceeding the command name with + the old command can still be used by preceding the command name with a double colon (eg ``::load``). It's not possible to redefine the commands ``:{``, ``:}`` and ``:!``. diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index d23681e0b3..7ba170845a 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -6956,7 +6956,7 @@ like this: client to deliberately override an instance from a library, without requiring a change to the library.) -- If all the remaining candidates are incoherent, the search suceeds, returning +- If all the remaining candidates are incoherent, the search succeeds, returning an arbitrary surviving candidate. - If more than one non-incoherent candidate remains, the search fails. @@ -8784,7 +8784,7 @@ injectivity of a type family: 5. In a *closed type family* all equations are ordered and in one place. Equations are also checked pair-wise but this time an equation has to - be paired with all the preceeding equations. Of course a + be paired with all the preceding equations. Of course a single-equation closed type family is trivially injective (unless (1), (2) or (3) above holds). diff --git a/docs/users_guide/safe_haskell.rst b/docs/users_guide/safe_haskell.rst index b95364531f..edfedda4b2 100644 --- a/docs/users_guide/safe_haskell.rst +++ b/docs/users_guide/safe_haskell.rst @@ -788,7 +788,7 @@ And five warning flags: .. index:: single: safe haskell imports, warning - The module ``A`` below is annotated to be explictly ``Safe``, but it imports + The module ``A`` below is annotated to be explicitly ``Safe``, but it imports ``Safe-Inferred`` module. :: {-# LANGUAGE Safe #-} diff --git a/hadrian/src/Hadrian/Builder.hs b/hadrian/src/Hadrian/Builder.hs index 5d645eea8c..fdfdb666ef 100644 --- a/hadrian/src/Hadrian/Builder.hs +++ b/hadrian/src/Hadrian/Builder.hs @@ -35,7 +35,7 @@ data BuildInfo = BuildInfo { buildOutputs :: [FilePath], -- | Options to be passed to Shake's 'cmd' function. buildOptions :: [CmdOption], - -- | Resources to be aquired. + -- | Resources to be acquired. buildResources :: [(Resource, Int)] } class ShakeValue b => Builder b where @@ -48,7 +48,7 @@ class ShakeValue b => Builder b where askBuilderWith :: b -> BuildInfo -> Action String -- | Runtime dependencies of a builder. For example, on Windows GHC requires - -- the utility @touchy.exe@ to be avilable on a specific path. + -- the utility @touchy.exe@ to be available on a specific path. runtimeDependencies :: b -> Action [FilePath] runtimeDependencies _ = return [] diff --git a/includes/HsFFI.h b/includes/HsFFI.h index 4b6278b518..32523b2c83 100644 --- a/includes/HsFFI.h +++ b/includes/HsFFI.h @@ -3,7 +3,7 @@ * (c) The GHC Team, 2000 * * A mapping for Haskell types to C types, including the corresponding bounds. - * Intended to be used in conjuction with the FFI. + * Intended to be used in conjunction with the FFI. * * WARNING: Keep this file and StgTypes.h in synch! * diff --git a/libraries/base/Data/IORef.hs b/libraries/base/Data/IORef.hs index 44769268cf..2886e594d3 100644 --- a/libraries/base/Data/IORef.hs +++ b/libraries/base/Data/IORef.hs @@ -49,7 +49,7 @@ mkWeakIORef r@(IORef (STRef r#)) (IO finalizer) = IO $ \s -> -- |Mutate the contents of an 'IORef'. -- -- Be warned that 'modifyIORef' does not apply the function strictly. This --- means if the program calls 'modifyIORef' many times, but seldomly uses the +-- means if the program calls 'modifyIORef' many times, but seldom uses the -- value, thunks will pile up in memory resulting in a space leak. This is a -- common mistake made when using an IORef as a counter. For example, the -- following will likely produce a stack overflow: diff --git a/libraries/base/Data/STRef.hs b/libraries/base/Data/STRef.hs index 5b8c6b7901..3636e6a8a6 100644 --- a/libraries/base/Data/STRef.hs +++ b/libraries/base/Data/STRef.hs @@ -40,7 +40,7 @@ import GHC.STRef -- "Hello, world!" -- -- Be warned that 'modifySTRef' does not apply the function strictly. This --- means if the program calls 'modifySTRef' many times, but seldomly uses the +-- means if the program calls 'modifySTRef' many times, but seldom uses the -- value, thunks will pile up in memory resulting in a space leak. This is a -- common mistake made when using an 'STRef' as a counter. For example, the -- following will leak memory and may produce a stack overflow: diff --git a/libraries/base/GHC/Event/Thread.hs b/libraries/base/GHC/Event/Thread.hs index a9d5410d9c..ad922d73f2 100644 --- a/libraries/base/GHC/Event/Thread.hs +++ b/libraries/base/GHC/Event/Thread.hs @@ -281,7 +281,7 @@ startIOManagerThread eventManagerArray i = do ThreadFinished -> create ThreadDied -> do -- Sanity check: if the thread has died, there is a chance - -- that event manager is still alive. This could happend during + -- that event manager is still alive. This could happened during -- the fork, for example. In this case we should clean up -- open pipes and everything else related to the event manager. -- See #4449 @@ -308,7 +308,7 @@ startTimerManagerThread = modifyMVar_ timerManagerThreadVar $ \old -> do ThreadFinished -> create ThreadDied -> do -- Sanity check: if the thread has died, there is a chance - -- that event manager is still alive. This could happend during + -- that event manager is still alive. This could happened during -- the fork, for example. In this case we should clean up -- open pipes and everything else related to the event manager. -- See #4449 diff --git a/libraries/base/GHC/List.hs b/libraries/base/GHC/List.hs index 9755f525ec..65fa4f54a5 100644 --- a/libraries/base/GHC/List.hs +++ b/libraries/base/GHC/List.hs @@ -400,7 +400,7 @@ strictUncurryScanr f pair = case pair of scanrFB :: (a -> b -> b) -> (b -> c -> c) -> a -> (b, c) -> (b, c) scanrFB f c = \x ~(r, est) -> (f x r, r `c` est) -- This lazy pattern match on the tuple is necessary to prevent --- an infinite loop when scanr recieves a fusable infinite list, +-- an infinite loop when scanr receives a fusable infinite list, -- which was the reason for #16943. -- See Note [scanrFB and evaluation] below diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs index a79f405079..14e4a9b7e2 100644 --- a/libraries/base/GHC/Read.hs +++ b/libraries/base/GHC/Read.hs @@ -414,7 +414,7 @@ readSymField fieldName readVal = do -- typecheck/TcGenDeriv.hs) would generate inline code for parsing fields; -- this, however, turned out to produce massive amounts of intermediate code, -- and produced a considerable performance hit in the code generator. --- Since Read instances are not generally supposed to be perfomance critical, +-- Since Read instances are not generally supposed to be performance critical, -- the readField and readSymField functions have been factored out, and the -- code generator now just generates calls rather than manually inlining the -- parsers. For large record types (e.g. 500 fields), this produces a diff --git a/libraries/base/System/CPUTime.hsc b/libraries/base/System/CPUTime.hsc index 6bc90f168a..5b0fdbf4da 100644 --- a/libraries/base/System/CPUTime.hsc +++ b/libraries/base/System/CPUTime.hsc @@ -40,7 +40,7 @@ import qualified System.CPUTime.Posix.ClockGetTime as I #elif defined(HAVE_GETRUSAGE) && ! solaris2_HOST_OS import qualified System.CPUTime.Posix.RUsage as I --- @getrusage()@ is right royal pain to deal with when targetting multiple +-- @getrusage()@ is right royal pain to deal with when targeting multiple -- versions of Solaris, since some versions supply it in libc (2.3 and 2.5), -- while 2.4 has got it in libucb (I wouldn't be too surprised if it was back -- again in libucb in 2.6..) diff --git a/libraries/base/tests/IO/T2122.hs b/libraries/base/tests/IO/T2122.hs index 488d2434bc..2969cdaf28 100644 --- a/libraries/base/tests/IO/T2122.hs +++ b/libraries/base/tests/IO/T2122.hs @@ -34,7 +34,7 @@ main = do writeFile fp "test" test True --- fails everytime when causeFailure is True in GHCi, with runhaskell, +-- fails every time when causeFailure is True in GHCi, with runhaskell, -- or when compiled. test :: Bool -> IO () test causeFailure = diff --git a/libraries/ghc-boot/GHC/BaseDir.hs b/libraries/ghc-boot/GHC/BaseDir.hs index 196ab2eb72..656e4014db 100644 --- a/libraries/ghc-boot/GHC/BaseDir.hs +++ b/libraries/ghc-boot/GHC/BaseDir.hs @@ -33,7 +33,7 @@ expandTopDir = expandPathVar "topdir" -- | @expandPathVar var value str@ -- --- replaces occurences of variable @$var@ with @value@ in str. +-- replaces occurrences of variable @$var@ with @value@ in str. expandPathVar :: String -> FilePath -> String -> String expandPathVar var value str | Just str' <- stripPrefix ('$':var) str diff --git a/libraries/ghci/GHCi/RemoteTypes.hs b/libraries/ghci/GHCi/RemoteTypes.hs index c024ae9fff..6a552f37da 100644 --- a/libraries/ghci/GHCi/RemoteTypes.hs +++ b/libraries/ghci/GHCi/RemoteTypes.hs @@ -33,7 +33,7 @@ import GHC.ForeignPtr -- Static pointers only; don't use this for heap-resident pointers. -- Instead use HValueRef. We will fix the remote pointer to be 64 bits. This -- should cover 64 and 32bit systems, and permits the exchange of remote ptrs --- between machines of different word size. For exmaple, when connecting to +-- between machines of different word size. For example, when connecting to -- an iserv instance on a different architecture with different word size via -- -fexternal-interpreter. newtype RemotePtr a = RemotePtr Word64 diff --git a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs index 461f213813..ef9a718111 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Ppr.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Ppr.hs @@ -788,7 +788,7 @@ instance Ppr Type where ppr (ForallT tvars ctxt ty) = sep [pprForall tvars ctxt, ppr ty] ppr (ForallVisT tvars ty) = sep [pprForallVis tvars [], ppr ty] ppr ty = pprTyApp (split ty) - -- Works, in a degnerate way, for SigT, and puts parens round (ty :: kind) + -- Works, in a degenerate way, for SigT, and puts parens round (ty :: kind) -- See Note [Pretty-printing kind signatures] instance Ppr TypeArg where ppr (TANormal ty) = ppr ty diff --git a/mk/project.mk.in b/mk/project.mk.in index 9ee2eab59f..21d5f6f683 100644 --- a/mk/project.mk.in +++ b/mk/project.mk.in @@ -142,7 +142,7 @@ else Windows_Host=NO endif -# Windows_Target=YES if we are targetting a Windows platform +# Windows_Target=YES if we are targeting a Windows platform ifneq "$(findstring $(TargetOS_CPP), mingw32)" "" Windows_Target=YES else diff --git a/rts/Apply.cmm b/rts/Apply.cmm index eeb760c5ed..dcfaa446f2 100644 --- a/rts/Apply.cmm +++ b/rts/Apply.cmm @@ -571,7 +571,7 @@ being carried out by TSO 2 and attempt to suspend it. The suspension process proceeds by invoking raiseAsync, which walks the stack from the top looking for update frames. For each update frame we take any stack -frames preceeding it and construct an AP_STACK heap object from them. We then +frames preceding it and construct an AP_STACK heap object from them. We then replace the updatee of the frame with an indirection pointing to the AP_STACK. So, after suspending the first update frame we have, @@ -373,7 +373,7 @@ freeHpcModuleInfo (HpcModuleInfo *mod) } /* Called at the end of execution, to write out the Hpc *.tix file - * for this exection. Safe to call, even if coverage is not used. + * for this execution. Safe to call, even if coverage is not used. */ void exitHpc(void) { diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index 5cd35f2e5b..0f47b82761 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -361,7 +361,7 @@ void freeSegments(ObjectCode *oc); #define MAP_ANONYMOUS MAP_ANON #endif -/* Which object file format are we targetting? */ +/* Which object file format are we targeting? */ #if defined(linux_HOST_OS) || defined(solaris2_HOST_OS) \ || defined(linux_android_HOST_OS) \ || defined(freebsd_HOST_OS) || defined(kfreebsdgnu_HOST_OS) \ diff --git a/rts/StgCRun.c b/rts/StgCRun.c index 934926e0f3..a6ef7054a4 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -131,7 +131,7 @@ STG_NO_OPTIMIZE StgWord8 *win32AllocStack(void) * ABI requires this (x64, Mac OSX 32bit/64bit) as well as interfacing with * other libraries through the FFI. * - * As part of this arrangment we must maintain the stack at a 16-byte boundary + * As part of this arrangement we must maintain the stack at a 16-byte boundary * - word_size-bytes (so 16n - 4 for i386 and 16n - 8 for x64) on entry to a * procedure since both GCC and LLVM expect this. This is because the stack * should have been 16-byte boundary aligned and then a call made which pushes diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 5ae7620fc7..12e84578fc 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -427,7 +427,7 @@ isGotLoad(struct relocation_info * ri) { /* This is very similar to makeSymbolExtra * However, as we load sections into different - * pages, that may be further appart than + * pages, that may be further apart than * branching allows, we'll use some extra * space at the end of each section allocated * for stubs. diff --git a/rts/linker/PEi386.c b/rts/linker/PEi386.c index 2f65f6a208..81308779a1 100644 --- a/rts/linker/PEi386.c +++ b/rts/linker/PEi386.c @@ -105,7 +105,7 @@ contain the name of the actual dll to load. This will be the only content of the section. In the symbol table, the last symbol will be the name used to refer to the dll in the relocation tables. This name will always - be in the format "symbol_name_iname", however when refered to, the format + be in the format "symbol_name_iname", however when referred to, the format "_head_symbol_name" is used. We record this symbol early on during GetNames and load the dll and use @@ -1535,7 +1535,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) } setImportSymbol (oc, sname); - /* Don't process this oc any futher. Just exit. */ + /* Don't process this oc any further. Just exit. */ oc->n_symbols = 0; oc->symbols = NULL; stgFree (oc->image); diff --git a/rts/sm/NonMoving.c b/rts/sm/NonMoving.c index 20ec5a45ba..d13989cc53 100644 --- a/rts/sm/NonMoving.c +++ b/rts/sm/NonMoving.c @@ -890,7 +890,7 @@ void nonmovingCollect(StgWeak **dead_weaks, StgTSO **resurrected_threads) // If we're interrupting or shutting down, do not let this capability go and // run a STW collection. Reason: we won't be able to acquire this capability // again for the sync if we let it go, because it'll immediately start doing - // a major GC, becuase that's what we do when exiting scheduler (see + // a major GC, because that's what we do when exiting scheduler (see // exitScheduler()). if (sched_state == SCHED_RUNNING) { concurrent_coll_running = true; diff --git a/rts/sm/NonMovingMark.c b/rts/sm/NonMovingMark.c index 085d7827df..3ebd039c43 100644 --- a/rts/sm/NonMovingMark.c +++ b/rts/sm/NonMovingMark.c @@ -88,7 +88,7 @@ memcount n_nonmoving_marked_compact_blocks = 0; * move the same large object to nonmoving_marked_large_objects more than once. */ static Mutex nonmoving_large_objects_mutex; -// Note that we don't need a similar lock for compact objects becuase we never +// Note that we don't need a similar lock for compact objects because we never // mark a compact object eagerly in a write barrier; all compact objects are // marked by the mark thread, so there can't be any races here. #endif diff --git a/testsuite/driver/perf_notes.py b/testsuite/driver/perf_notes.py index cfbd5e529f..cebb8f9815 100644 --- a/testsuite/driver/perf_notes.py +++ b/testsuite/driver/perf_notes.py @@ -517,7 +517,7 @@ def get_commit_metric(gitNoteRef, # tolerance_dev: allowed deviation of the actual value from the expected value. # allowed_perf_changes: allowed changes in stats. This is a dictionary as returned by get_allowed_perf_changes(). # force_print: Print stats even if the test stat was in the tolerance range. -# Returns a (MetricChange, pass/fail object) tuple. Passes if the stats are withing the expected value ranges. +# Returns a (MetricChange, pass/fail object) tuple. Passes if the stats are within the expected value ranges. def check_stats_change(actual: PerfStat, baseline: Baseline, tolerance_dev, diff --git a/testsuite/driver/testglobals.py b/testsuite/driver/testglobals.py index c39ca7a8c9..2393247b22 100644 --- a/testsuite/driver/testglobals.py +++ b/testsuite/driver/testglobals.py @@ -133,7 +133,7 @@ class TestConfig: # Do we have SMP support? self.have_smp = False - # Is gdb avaliable? + # Is gdb available? self.have_gdb = False # Is readelf available? diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 79d504a845..07206799c1 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1379,7 +1379,7 @@ def metric_dict(name, way, metric, value) -> PerfStat: # way: the way. # stats_file: the path of the stats_file containing the stats for the test. # range_fields: see TestOptions.stats_range_fields -# Returns a pass/fail object. Passes if the stats are withing the expected value ranges. +# Returns a pass/fail object. Passes if the stats are within the expected value ranges. # This prints the results for the user. def check_stats(name: TestName, way: WayName, diff --git a/testsuite/tests/concurrent/prog001/Arithmetic.hs b/testsuite/tests/concurrent/prog001/Arithmetic.hs index a1253969b0..bce3ff6400 100644 --- a/testsuite/tests/concurrent/prog001/Arithmetic.hs +++ b/testsuite/tests/concurrent/prog001/Arithmetic.hs @@ -32,7 +32,7 @@ plusOne (0:xs) = 1:fl xs --- Substraction by 1, the input must be in (0,1) +-- Subtraction by 1, the input must be in (0,1) minusOne :: Gray -> Gray minusOne (1:xs) = 0:fl xs diff --git a/testsuite/tests/cps/cps021.cmm b/testsuite/tests/cps/cps021.cmm index fa7e809ee0..db67d97da2 100644 --- a/testsuite/tests/cps/cps021.cmm +++ b/testsuite/tests/cps/cps021.cmm @@ -1,4 +1,4 @@ -// Verify jumping to the begining of the current continuation +// Verify jumping to the beginning of the current continuation // is done with a branch and not a jump foo() { diff --git a/testsuite/tests/deSugar/should_compile/T12944.hs b/testsuite/tests/deSugar/should_compile/T12944.hs index 076812d6e7..540ea06e81 100644 --- a/testsuite/tests/deSugar/should_compile/T12944.hs +++ b/testsuite/tests/deSugar/should_compile/T12944.hs @@ -31,7 +31,7 @@ instance (AdditiveGroup (poly a), Num a) => AdditiveGroup (IntOfLog poly a) wher IntOfLog k p ^+^ IntOfLog k' p' = IntOfLog (k + k') (p ^+^ p') negateV (IntOfLog k p) = IntOfLog (negate k) (negateV p) {-# SPECIALISE instance Num a => AdditiveGroup (IntOfLog Poly1 a) #-} - -- This pragmas casued the crash + -- This pragmas caused the crash instance (VectorSpace (poly a), Scalar (poly a) ~ a, Num a) => VectorSpace (IntOfLog poly a) where type Scalar (IntOfLog poly a) = a diff --git a/testsuite/tests/deriving/should_fail/T7148a.hs b/testsuite/tests/deriving/should_fail/T7148a.hs index 6441058b24..fd4a8fcda6 100644 --- a/testsuite/tests/deriving/should_fail/T7148a.hs +++ b/testsuite/tests/deriving/should_fail/T7148a.hs @@ -19,7 +19,7 @@ instance Convert (SAFE a) where newtype IS_NO_LONGER a = IS_NO_LONGER a deriving Convert type instance Result (IS_NO_LONGER a) b = b ---infered type is +--inferred type is unsafeCoerce :: forall a b. a -> b unsafeCoerce = coerce (Proxy :: Proxy b) . IS_NO_LONGER . SAFE @@ -34,4 +34,4 @@ crash = unsafeCoerce . tail . tail . tail . unsafeCoerce $ True --time for side effects unsafePerformIO :: IO a -> a -unsafePerformIO x = runST $ unsafeCoerce x
\ No newline at end of file +unsafePerformIO x = runST $ unsafeCoerce x diff --git a/testsuite/tests/module/mod183.stderr b/testsuite/tests/module/mod183.stderr index cf7fdf4fa0..5f3c131537 100644 --- a/testsuite/tests/module/mod183.stderr +++ b/testsuite/tests/module/mod183.stderr @@ -1 +1 @@ -mod183.hs:5:26: Multiple occurences of 'qualified' +mod183.hs:5:26: Multiple occurrences of 'qualified' diff --git a/testsuite/tests/perf/should_run/T8763.hs b/testsuite/tests/perf/should_run/T8763.hs index 90c4436ce9..fac6e6302a 100644 --- a/testsuite/tests/perf/should_run/T8763.hs +++ b/testsuite/tests/perf/should_run/T8763.hs @@ -1,7 +1,7 @@ -- | The fusion helper for @enumFromThenTo \@Int@ had multiple --- occurences of @c@, which made the simplifier refuse to inline it. +-- occurrences of @c@, which made the simplifier refuse to inline it. -- The new implementation for @efdtInt{Up,Dn}FB@ only have a single --- occurence of @c@ which the simplifier inlines unconditionally. +-- occurrence of @c@ which the simplifier inlines unconditionally. module Main (main) where import Control.Monad (when, forM_) @@ -12,7 +12,7 @@ nop _ = return () {-# NOINLINE nop #-} -- This is the baseline, using @enumFromTo@ which already had only a --- single occurence of @c@. +-- single occurrence of @c@. f :: Int -> ST s () f n = do diff --git a/testsuite/tests/programs/andy_cherry/DataTypes.hs b/testsuite/tests/programs/andy_cherry/DataTypes.hs index bcb6cbcf60..01df7f5abd 100644 --- a/testsuite/tests/programs/andy_cherry/DataTypes.hs +++ b/testsuite/tests/programs/andy_cherry/DataTypes.hs @@ -13,7 +13,7 @@ class Presentable a where - userFormat :: a -> String -- in prefered display format + userFormat :: a -> String -- in preferred display format diff --git a/testsuite/tests/programs/seward-space-leak/Main.lhs b/testsuite/tests/programs/seward-space-leak/Main.lhs index 6c3f9f9d32..fb1527e330 100644 --- a/testsuite/tests/programs/seward-space-leak/Main.lhs +++ b/testsuite/tests/programs/seward-space-leak/Main.lhs @@ -97,7 +97,7 @@ parameter numbering starts at 1). @Call@. Calls to other functions are done with @Call@, which expects the callee to return @Zero@ or @One@, and selects the relevant -branch. The @Tag@s identify calls in the dependancy list. +branch. The @Tag@s identify calls in the dependency list. Although a @Call@ is a glorified @Case@ statement, the only allowed return values are @Zero@ and @One@. Hence the @CDS CDS@ continuations rather than the more comprehensive @(AList Return CDS)@. @@ -166,7 +166,7 @@ as necessary. ToDo: Need to rename call sites? I don't think so. Main CDS evaluator takes \begin{itemize} \item the code store -\item the dependancy list, a list of @Tag@s of calls which are +\item the dependency list, a list of @Tag@s of calls which are currently in progress \item the current arguments \item the CDS fragment currently being worked on diff --git a/testsuite/tests/safeHaskell/check/Check06.hs b/testsuite/tests/safeHaskell/check/Check06.hs index a4debfc2cb..99649fa079 100644 --- a/testsuite/tests/safeHaskell/check/Check06.hs +++ b/testsuite/tests/safeHaskell/check/Check06.hs @@ -1,7 +1,7 @@ {-# LANGUAGE Trustworthy, NoImplicitPrelude #-} {-# OPTIONS_GHC -fpackage-trust #-} --- make sure importing a safe-infered module brings in the +-- make sure importing a safe-inferred module brings in the -- pkg trust requirements correctly. module Check06 ( main' ) where diff --git a/testsuite/tests/safeHaskell/check/Check06_A.hs b/testsuite/tests/safeHaskell/check/Check06_A.hs index 9c9d92ba24..4cda329fec 100644 --- a/testsuite/tests/safeHaskell/check/Check06_A.hs +++ b/testsuite/tests/safeHaskell/check/Check06_A.hs @@ -1,4 +1,4 @@ --- safe infered, with requirement base is trusted +-- safe inferred, with requirement base is trusted module Check06_A where mainM :: Int -> Int diff --git a/testsuite/tests/safeHaskell/check/Check07_A.hs b/testsuite/tests/safeHaskell/check/Check07_A.hs index 5b38c6a07b..efc58e0bfe 100644 --- a/testsuite/tests/safeHaskell/check/Check07_A.hs +++ b/testsuite/tests/safeHaskell/check/Check07_A.hs @@ -1,6 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} --- safe infered, with no pkg trust reqs +-- safe inferred, with no pkg trust reqs module Check07_A where a :: a -> a diff --git a/testsuite/tests/safeHaskell/check/Check07_B.hs b/testsuite/tests/safeHaskell/check/Check07_B.hs index 4a2003f9a9..5085cc18ab 100644 --- a/testsuite/tests/safeHaskell/check/Check07_B.hs +++ b/testsuite/tests/safeHaskell/check/Check07_B.hs @@ -1,4 +1,4 @@ --- safe infered, with requirement base is trusted +-- safe inferred, with requirement base is trusted module Check07_B where import Prelude diff --git a/testsuite/tests/safeHaskell/check/Check08_A.hs b/testsuite/tests/safeHaskell/check/Check08_A.hs index c888a59b71..4438a34e09 100644 --- a/testsuite/tests/safeHaskell/check/Check08_A.hs +++ b/testsuite/tests/safeHaskell/check/Check08_A.hs @@ -1,6 +1,6 @@ {-# LANGUAGE NoImplicitPrelude #-} --- safe infered, with no pkg trust reqs +-- safe inferred, with no pkg trust reqs module Check08_A where a :: a -> a diff --git a/testsuite/tests/safeHaskell/check/Check08_B.hs b/testsuite/tests/safeHaskell/check/Check08_B.hs index 41feab5eae..42d01f2b33 100644 --- a/testsuite/tests/safeHaskell/check/Check08_B.hs +++ b/testsuite/tests/safeHaskell/check/Check08_B.hs @@ -1,4 +1,4 @@ --- safe infered, with requirement base is trusted +-- safe inferred, with requirement base is trusted module Check08_B where import Prelude diff --git a/testsuite/tests/safeHaskell/check/all.T b/testsuite/tests/safeHaskell/check/all.T index 47e875d3be..8cf37d3b43 100644 --- a/testsuite/tests/safeHaskell/check/all.T +++ b/testsuite/tests/safeHaskell/check/all.T @@ -41,7 +41,7 @@ test('Check04', normal, multi_compile, ['Check04', [ # Check -fpackage-trust with no safe haskell flag is an error test('Check05', normal, compile, ['']) -# Check safe-infered modules have correct pkg trust requirements +# Check safe-inferred modules have correct pkg trust requirements test('Check06', [], multimod_compile_fail, ['Check06', '']) # Check selective safe imports bring in correct pkg trust requirements diff --git a/testsuite/tests/safeHaskell/check/pkg01/M_SafePkg5.hs b/testsuite/tests/safeHaskell/check/pkg01/M_SafePkg5.hs index a4b7390352..75bde26b4e 100644 --- a/testsuite/tests/safeHaskell/check/pkg01/M_SafePkg5.hs +++ b/testsuite/tests/safeHaskell/check/pkg01/M_SafePkg5.hs @@ -1,6 +1,6 @@ -- safe inference -- same module as M_SafePkg4 which compiles with -XSafe. --- Want to make sure compiles fine and is infered safe and +-- Want to make sure compiles fine and is inferred safe and -- also picks up corrected pkg trust requirements. module M_SafePkg5 where diff --git a/testsuite/tests/safeHaskell/flags/SafeFlags21.hs b/testsuite/tests/safeHaskell/flags/SafeFlags21.hs index c7e8b0d87a..5169a03583 100644 --- a/testsuite/tests/safeHaskell/flags/SafeFlags21.hs +++ b/testsuite/tests/safeHaskell/flags/SafeFlags21.hs @@ -1,6 +1,6 @@ {-# OPTIONS_GHC -fwarn-unsafe #-} -- | Basic test to see if Safe warning flags compile --- Warn if module is infered unsafe +-- Warn if module is inferred unsafe -- In this test the warning _shouldn't_ fire module SafeFlags21 where diff --git a/testsuite/tests/typecheck/should_compile/tc163.hs b/testsuite/tests/typecheck/should_compile/tc163.hs index 21d8a72949..fb8682bc22 100644 --- a/testsuite/tests/typecheck/should_compile/tc163.hs +++ b/testsuite/tests/typecheck/should_compile/tc163.hs @@ -24,7 +24,7 @@ flop = \m' k -> mkM3' m' (\bm k1 -> error "urk") -- But if we give mkM3' the type -- forall a r. M3' a -> (forall b. ...) -> r --- everthing works fine. Very very delicate. +-- everything works fine. Very very delicate. ---------------- A more complex case ------------- bind :: M3 a -> (a -> M3 b) -> M3 b diff --git a/testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.hs b/testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.hs index 566f8aa102..982d7e596c 100644 --- a/testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.hs +++ b/testsuite/tests/typecheck/should_compile/type_in_type_hole_fits.hs @@ -55,7 +55,7 @@ newtype Sorted (cpu :: AsympPoly) -- The minimum operational complexity -- Merge sort is O(N*Log(N)) on average in complexity, so that's the -- minimum complexity we promise to satisfy. Same goes with memory, which is --- O(N), and as we all know, mergesort is a stable sorting algoritm. +-- O(N), and as we all know, mergesort is a stable sorting algorithm. mergeSort :: (Ord a, n >=. O(N*.LogN), m >=. O(N), IsStable s) => [a] -> Sorted n m s a mergeSort = Sorted . sort diff --git a/utils/genapply/Main.hs b/utils/genapply/Main.hs index 8c194f1ca0..a6d944efa4 100644 --- a/utils/genapply/Main.hs +++ b/utils/genapply/Main.hs @@ -38,7 +38,7 @@ import System.IO import Control.Arrow ((***)) -- ----------------------------------------------------------------------------- --- Argument kinds (rougly equivalent to PrimRep) +-- Argument kinds (roughly equivalent to PrimRep) data ArgRep = N -- non-ptr diff --git a/utils/lndir/lndir-Xos.h b/utils/lndir/lndir-Xos.h index b423f6b641..6421d4a0bf 100644 --- a/utils/lndir/lndir-Xos.h +++ b/utils/lndir/lndir-Xos.h @@ -18,7 +18,7 @@ */ /* This is a collection of things to try and minimize system dependencies - * in a "signficant" number of source files. + * in a "significant" number of source files. */ #pragma once diff --git a/utils/unlit/unlit.c b/utils/unlit/unlit.c index 97f853b268..5a0e535109 100644 --- a/utils/unlit/unlit.c +++ b/utils/unlit/unlit.c @@ -20,7 +20,7 @@ * 1) Empty script files are not permitted. A file in which no lines * begin with `>' usually indicates a file in which the programmer * has forgotten about the literate script convention. - * 2) A line containing part of program definition (i.e. preceeded by `>') + * 2) A line containing part of program definition (i.e. preceded by `>') * cannot be used immediately before or after a comment line unless * the comment line is blank. This error usually indicates that * the `>' character has been omitted from a line in a section of @@ -166,7 +166,7 @@ static int egetc(FILE *istream) * Lines of type DEFN are copied to the output stream `ostream' * (without the leading DEFNCHAR). BLANK and TEXT lines are * replaced by empty (i.e. blank lines) in the output stream, so - * that error messages refering to line numbers in the output file + * that error messages referring to line numbers in the output file * can also be used to locate the corresponding line in the input * stream. */ |