compiler typos
compiler/GHC/Core/Opt/DmdAnal.hs
compiler/GHC/Core/Opt/WorkWrap/Utils.hs
compiler/GHC/Parser/Errors/Types.hs
compiler/GHC/Driver/Flags.hs
compiler/GHC/Tc/Types/Constraint.hs
should line 1948 be edited
$ perl -ne 'print if $. == 1941 .. 1949' ghc/compiler/GHC/Core/Opt/DmdAnal.hs
-- In the initial iteration for f, f=Bot
-- Suppose h is found to be strict in z, but the occurrence of g in its RHS
-- is lazy. Now consider the fixpoint iteration for g, esp the demands it
-- places on its free variables. Suppose it places none. Then the
-- x `fatbar` ...call to h...
-- will give a x->V demand for x. That turns into a L demand for x,
-- which floats out of the defn for h. Without the modifyEnv, that
-- L demand doesn't get both'd with the Bot coming up from the inner
-- call to f. So we just get an L demand for x for g.
$
what's the replacement string for can'easily
$ perl -ne 'print if $. == 722 .. 724' ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
This warning also triggers for the stream fusion library within `text`.
We can'easily W/W constructed results like `Stream` because we have no simple
way to express existential types in the worker's type signature.
$
sed -i "s/can'easily/can't easily/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
or
sed -i "s/can'easily/can easily/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs
should binded
be replaced with bound
$ grep -nr binded ghc/compiler
ghc/compiler/GHC/Parser/Errors/Types.hs:499: -- pattern with the binded operator name
$
sed -i "s/binded/bound/g" ghc/compiler/GHC/Parser/Errors/Types.hs
my presumption is alleviate
is the replacement string
$ grep -nr elivate ghc/compiler
ghc/compiler/GHC/Driver/Flags.hs:363: -- this should elivate the excessive command line limit restrictions
$
sed -i "s/elivate/alleviate/g" ghc/compiler/GHC/Driver/Flags.hs
my presumption is fresh
is the replacement string
$ perl -ne 'print if $. == 1560 .. 1561' ghc/compiler/GHC/Tc/Types/Constraint.hs
* The skolem variables bound in ic_skols are all freah when the
implication is created.
$
sed -i "s/freah/fresh/g" ghc/compiler/GHC/Tc/Types/Constraint.hs
- Show closed items
Related merge requests 2
When these merge requests are accepted, this issue will be closed automatically.
- !8720
Activity
-
Newest first Oldest first
-
Show all activity Show comments only Show history only
- ghc-triage-bot added needs triage label
added needs triage label
- Ghost User changed the description
Compare with previous version changed the description
- sheaf added Plow Ttask documentation labels
added Plow Ttask documentation labels
- sheaf removed needs triage label
removed needs triage label
- Author Contributor
my presumption is
integration
is the replacement string$ grep -nr interation ghc/compiler ghc/compiler/GHC/HsToCore/Expr.hs:328:For a user written Integer instance we can't predict the interation of negate and fromIntegral. $
sed -i "s/interation/integration/g" ghc/compiler/GHC/HsToCore/Expr.hs
my presumption is
nonexisting
is the replacement string$ grep -nr noexisting ghc/compiler ghc/compiler/GHC/CmmToAsm/CFG.hs:417: edgeWeight $ expectJust "Edgeweight for noexisting block" $ ghc/compiler/GHC/CmmToAsm/CFG.hs:421:getTransitionSource from to cfg = transitionSource $ expectJust "Source info for noexisting block" $ $
sed -i "s/noexisting/nonexisting/g" ghc/compiler/GHC/CmmToAsm/CFG.hs
what's the replacement string for
pached-fixup
$ grep -nr pached ghc/compiler ghc/compiler/GHC/CmmToAsm/Reg/Linear.hs:621:-- pprTrace "pached-fixup" ((ppr fixup_blocks)) $ do $
sed -i "s/pached/patched/g" ghc/compiler/GHC/CmmToAsm/Reg/Linear.hs
my presumption is
pointed.
is the replacement string$ perl -ne 'print if $. == 838 .. 840' ghc/compiler/GHC/Runtime/Heap/Inspect.hs -- In such case, we return a best approximation: -- ignore the unpointed args, and recover the pointeds -- This preserves laziness, and should be safe. $
sed -i "s/pointeds/pointed./g" ghc/compiler/GHC/Runtime/Heap/Inspect.hs
my presumption is
propagate
is the replacement string$ grep -nr propate ghc/compiler ghc/compiler/GHC/Core/Opt/CSE.hs:147:it to the simplifier to propate effects to the RULES. Finally, it $
sed -i "s/propate/propagate/g" ghc/compiler/GHC/Core/Opt/CSE.hs
- Developer
Hi Eric,
- can't easily
- Yes, bound
- Yes, alleviate
- Yes, fresh
- interaction
- Yes, nonexisting
- patched-fixup
- I would use "pointed ones"
- Yes, propagate
- Author Contributor
won't fix
keeness
$ perl -ne 'print if $. == 2810 .. 2812' ghc/compiler/GHC/Driver/Session.hs , make_dep_flag defFlag "funfolding-keeness-factor" (floatSuffix (\_ d -> d)) "-funfolding-keeness-factor is no longer respected as of GHC 9.0" $ grep -nr keeness ghc/docs ghc/docs/users_guide/using-optimisation.rst:1554:.. ghc-flag:: -funfolding-keeness-factor=⟨n⟩ $
this is awkward
$ grep -nr punctuations ghc/compiler ghc/compiler/GHC/Parser/Annotation.hs:650:-- more trailing punctuations items, such as commas or semicolons. $
this was written 15 years ago by a Spanish coder
my presumption is
collect
is the replacement string$ grep -nr recopilate ghc/compiler ghc/compiler/GHC/Runtime/Debugger.hs:164:-- Processing suspensions. Give names and recopilate info $
sed -i "s/recopilate/collect/g" ghc/compiler/GHC/Runtime/Debugger.hs
recopilate
recopilar
v. compile, collect, gather together in one place; compose (an essay, book, etc.)untractable
is an archaic word for intractable$ grep -nr untractable ghc/compiler ghc/compiler/GHC/HsToCore/Pmc/Solver.hs:1944:(see Note [Implementation of COMPLETE pragmas]). That is untractable for an $
- Author Contributor
grepable
is the more common spelling
parameterised
/parameterized
is the more common spelling
whodunit
is the more common spelling$ wc -l typos.sh 384 typos.sh $ cat typos.sh #!/bin/sh sed -i "s/Accessessors/Accessors/g" ghc/compiler/GHC/Settings.hs sed -i "s/Accessessors/Accessors/g" ghc/compiler/GHC/Driver/Session.hs sed -i "s/Acumulating/Accumulating/g" ghc/compiler/GHC/Core/TyCo/FVs.hs sed -i "s/Analsysis/Analysis/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/Calcuate/Calculate/g" ghc/compiler/GHC/Core/Opt/SpecConstr.hs sed -i "s/Comprension/Comprehension/g" ghc/compiler/GHC/HsToCore/Match.hs sed -i "s/Catenate/Concatenate/g" ghc/compiler/GHC/Utils/Outputable.hs sed -i "s/Coalesences/Coalescences/g" ghc/compiler/GHC/CmmToAsm/Reg/Graph.hs sed -i "s/Consdider/Consider/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/Consequnce/Consequence/g" ghc/compiler/GHC/Types/Demand.hs sed -i "s/Constrast/Contrast/g" ghc/compiler/GHC/Types/SrcLoc.hs sed -i "s/Decicdes/Decides/g" ghc/compiler/GHC/Cmm/CLabel.hs sed -i "s/Dicsussion/Discussion/g" ghc/compiler/GHC/Tc/Utils/TcMType.hs sed -i "s/Divergenge/Divergence/g" ghc/compiler/GHC/Core/Opt/Arity.hs sed -i "s/Eample/Example/g" ghc/compiler/GHC/Core/TyCon.hs sed -i "s/Exammples/Examples/g" ghc/compiler/GHC/Core/Opt/SetLevels.hs sed -i "s/Exammples/Examples/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/Exemple/Example/g" ghc/compiler/GHC/Tc/Utils/Instantiate.hs sed -i "s/Explict/Explicit/g" ghc/compiler/GHC/Tc/Gen/Expr.hs sed -i "s/INLINEALE/INLINEABLE/g" ghc/compiler/GHC/Core/Unfold/Make.hs sed -i "s/(IPE)/(IPEs)/g" ghc/compiler/GHC/Driver/GenerateCgIPEStub.hs sed -i "s/Missmatched/Mismatched/g" ghc/compiler/GHC/Stg/InferTags/Rewrite.hs sed -i "s/Neglible/Negligible/g" ghc/compiler/GHC/StgToCmm/Expr.hs sed -i "s/NoOccurence/NoOccurrence/g" ghc/compiler/GHC/Rename/Env.hs sed -i "s/Notebly/Notably/g" ghc/compiler/GHC/Tc/Types/Evidence.hs sed -i "s/Operang/Operand/g" ghc/compiler/GHC/CmmToAsm/AArch64/Instr.hs sed -i "s/Orderd/Ordered/g" ghc/compiler/GHC/CmmToAsm/AArch64/Ppr.hs sed -i "s/Prerecondition/Precondition/g" ghc/compiler/GHC/Types/Name/Reader.hs sed -i "s/Provernance/Provenance/g" ghc/compiler/GHC/Driver/GenerateCgIPEStub.hs sed -i "s/Retuerns/Returns/g" ghc/compiler/GHC/IfaceToCore.hs sed -i "s/Seperates/Separates/g" ghc/compiler/GHC/Hs/DocString.hs sed -i "s/Stastics/Statistics/g" ghc/compiler/GHC/Unit/External.hs sed -i "s/Supposably/Supposedly/g" ghc/compiler/GHC/Data/Graph/Ops.hs sed -i "s/Unforunately/Unfortunately/g" ghc/compiler/GHC/Core/TyCo/Rep.hs sed -i "s/Universially/Universally/g" ghc/compiler/GHC/Core/PatSyn.hs sed -i "s/absolultely/absolutely/g" ghc/compiler/GHC/Tc/Validity.hs sed -i "s/accidently/accidentally/g" ghc/compiler/GHC/Driver/Env/KnotVars.hs sed -i "s/accomodate/accommodate/g" ghc/compiler/GHC/HsToCore/Pmc.hs sed -i "s/accomodating/accommodating/g" ghc/compiler/Language/Haskell/Syntax/Expr.hs sed -i "s/adjancet/adjacent/g" ghc/compiler/GHC/Data/Graph/UnVar.hs sed -i "s/adventageous/advantageous/g" ghc/compiler/GHC/Data/Graph/Ops.hs sed -i "s/aggresive/aggressive/g" ghc/compiler/GHC/Tc/Deriv/Generics.hs sed -i "s/ambiant/ambient/g" ghc/compiler/GHC/Core/Opt/ConstantFold.hs sed -i "s/ambiant/ambient/g" ghc/compiler/GHC/SysTools/BaseDir.hs sed -i "s/ambigious/ambiguous/g" ghc/compiler/GHC/Prelude.hs sed -i "s/amibient/ambient/g" ghc/compiler/GHC/Tc/Utils/Unify.hs sed -i "s/analayis/analysis/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/applictions/applications/g" ghc/compiler/GHC/Core/Opt/Arity.hs sed -i "s/appling/applying/g" ghc/compiler/GHC/Tc/Solver/InertSet.hs sed -i "s/appplications/applications/g" ghc/compiler/GHC/Tc/Gen/Expr.hs sed -i "s/appropiate/appropriate/g" ghc/compiler/GHC/Driver/Make.hs sed -i "s/appropiately/appropriately/g" ghc/compiler/GHC/Unit/Env.hs sed -i "s/argement/argument/g" ghc/compiler/GHC/Core/Coercion.hs sed -i "s/arguemnt/argument/g" ghc/compiler/GHC/Tc/Utils/Unify.hs sed -i "s/arugment/argument/g" ghc/compiler/GHC/Tc/Validity.hs sed -i "s/arument/argument/g" ghc/compiler/GHC/Tc/Gen/App.hs sed -i "s/assignemnts/assignments/g" ghc/compiler/GHC/Cmm/Sink.hs sed -i "s/assmebly/assembly/g" ghc/compiler/GHC/CmmToAsm/AArch64/CodeGen.hs sed -i "s/attemps/attempts/g" ghc/compiler/GHC/Driver/Session.hs sed -i "s/augmennt/augment/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/automomatically/automatically/g" ghc/compiler/GHC/CmmToAsm/AArch64/CodeGen.hs sed -i "s/auxiliar/auxiliary/g" ghc/compiler/GHC/Runtime/Heap/Inspect.hs sed -i "s/becuase/because/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/becuase/because/g" ghc/compiler/GHC/Core/RoughMap.hs sed -i "s/becuase/because/g" ghc/compiler/GHC/Types/Literal.hs sed -i "s/beeen/been/g" ghc/compiler/GHC/Driver/Make.hs sed -i "s/beteen/between/g" ghc/compiler/GHC/Tc/Errors/Types.hs sed -i "s/betweeen/between/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/beucase/because/g" ghc/compiler/GHC/Tc/Gen/Bind.hs sed -i "s/beyong/beyond/g" ghc/compiler/GHC/Core/Opt/Simplify/Utils.hs sed -i "s/binded/bound/g" ghc/compiler/GHC/Parser/Errors/Types.hs sed -i "s/bosed/boxed/g" ghc/compiler/GHC/Builtin/Types.hs sed -i "s/bottomming/bottoming/g" ghc/compiler/GHC/Core/Opt/Arity.hs sed -i "s/botttom/bottom/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/breakders/breakers/g" ghc/compiler/GHC/Core/Opt/OccurAnal.hs sed -i "s/breathren/brethren/g" ghc/compiler/GHC/Builtin/PrimOps.hs sed -i "s/bulletted/bulleted/g" ghc/compiler/GHC/Tc/Errors/Types.hs sed -i "s/but's/but/g" ghc/compiler/GHC/Tc/Errors/Types.hs sed -i "s/calcuates/calculates/g" ghc/compiler/GHC/Rename/Expr.hs sed -i "s/can'easily/can't easily/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/carefullly/carefully/g" ghc/compiler/GHC/Core/Opt/Pipeline.hs sed -i "s/clase/class/g" ghc/compiler/GHC/Tc/Validity.hs sed -i "s/clases/classes/g" ghc/compiler/GHC/Runtime/Eval.hs sed -i "s/clases/classes/g" ghc/compiler/GHC/Tc/Types.hs sed -i "s/coalesence/coalescence/g" ghc/compiler/GHC/Data/Graph/Ops.hs sed -i "s/coalesence/coalescence/g" ghc/compiler/GHC/CmmToAsm/Reg/Graph.hs sed -i "s/coelesce/coalesce/g" ghc/compiler/GHC/Data/Graph/Ops.hs sed -i "s/comopare/compare/g" ghc/compiler/GHC/Tc/Deriv/Generate.hs sed -i "s/comoponent/component/g" ghc/compiler/GHC/Rename/Module.hs sed -i "s/compatability/compatibility/g" ghc/compiler/GHC.hs sed -i "s/compilicated/complicated/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/comprehesion/comprehension/g" ghc/compiler/GHC/Tc/Types/Origin.hs sed -i "s/compuation/computation/g" ghc/compiler/GHC/CmmToAsm/AArch64/Ppr.hs sed -i "s/concatening/concatenating/g" ghc/compiler/GHC/CmmToAsm/CPrim.hs sed -i "s/concatentating/concatenating/g" ghc/compiler/GHC/Types/RepType.hs sed -i "s/concatinate/concatenate/g" ghc/compiler/GHC/SysTools/Ar.hs sed -i "s/conposition/composition/g" ghc/compiler/GHC/Utils/Outputable.hs sed -i "s/consistnecy/consistency/g" ghc/compiler/GHC/Core/FamInstEnv.hs sed -i "s/constracting/constructing/g" ghc/compiler/GHC/ByteCode/Instr.hs sed -i "s/continguous/contiguous/g" ghc/compiler/GHC/Hs/DocString.hs sed -i "s/contradicatory/contradictory/g" ghc/compiler/GHC/Tc/Instance/FunDeps.hs sed -i "s/contraints/constraints/g" ghc/compiler/GHC/Tc/Solver.hs sed -i "s/contraints/constraints/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/corrolary/corollary/g" ghc/compiler/GHC/Tc/Types.hs sed -i "s/corrresponds/corresponds/g" ghc/compiler/GHC/Core/Opt/SpecConstr.hs sed -i "s/counter intutive/counter-intuitive/g" ghc/compiler/GHC/CmmToAsm/AArch64/CodeGen.hs sed -i "s/critially/critically/g" ghc/compiler/GHC/Core/TyCo/FVs.hs sed -i "s/currenly/currently/g" ghc/compiler/GHC/Types/Id/Make.hs sed -i "s/currrently/currently/g" ghc/compiler/GHC/Core/Opt/Arity.hs sed -i "s/decicions/decisions/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/declaraations/declarations/g" ghc/compiler/GHC/Rename/Module.hs sed -i "s/declaractions/declarations/g" ghc/compiler/GHC/Rename/Bind.hs sed -i "s/decomopose/decompose/g" ghc/compiler/GHC/Tc/Solver/Canonical.hs sed -i "s/degredation/degradation/g" ghc/compiler/GHC/StgToCmm/Monad.hs sed -i "s/demanand/demand/g" ghc/compiler/GHC/Core/Opt/OccurAnal.hs sed -i "s/depdendency/dependency/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/dependecy/dependency/g" ghc/compiler/GHC/Rename/Names.hs sed -i "s/descovered/discovered/g" ghc/compiler/GHC/Driver/MakeFile.hs sed -i "s/determinded/determined/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/deterministicly/deterministically/g" ghc/compiler/GHC/Tc/Instance/Family.hs sed -i "s/dicionary/dictionary/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/dicussion/discussion/g" ghc/compiler/GHC/Core/Coercion.hs sed -i "s/disjuctive/disjunctive/g" ghc/compiler/GHC/Types/Hint.hs sed -i "s/distict/distinct/g" ghc/compiler/GHC/Driver/GenerateCgIPEStub.hs sed -i "s/distinguisable/distinguishable/g" ghc/compiler/GHC/Iface/Recomp.hs sed -i "s/dito/ditto/g" ghc/compiler/GHC/StgToCmm/Lit.hs sed -i "s/doesnt/doesn't/g" ghc/compiler/GHC/Tc/Errors/Types.hs sed -i "s/easist/easiest/g" ghc/compiler/GHC/Core/Opt/SpecConstr.hs sed -i "s/effiency/efficiency/g" ghc/compiler/GHC/Data/Stream.hs sed -i "s/elaboarate/elaborate/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/elivate/alleviate/g" ghc/compiler/GHC/Driver/Flags.hs sed -i "s/emascuated/emasculated/g" ghc/compiler/GHC/Types/Demand.hs sed -i "s/encloseing/enclosing/g" ghc/compiler/GHC/Rename/Env.hs sed -i "s/enfore/enforce/g" ghc/compiler/GHC/Stg/InferTags/Rewrite.hs sed -i "s/entires/entries/g" ghc/compiler/GHC/Runtime/Context.hs sed -i "s/entitites/entities/g" ghc/compiler/GHC/Unit.hs sed -i "s/environement/environment/g" ghc/compiler/GHC/Runtime/Eval.hs sed -i "s/environements/environments/g" ghc/compiler/GHC/Core/Multiplicity.hs sed -i "s/environemnt/environment/g" ghc/compiler/GHC/Driver/Env/KnotVars.hs sed -i "s/equivalant/equivalent/g" ghc/compiler/Language/Haskell/Syntax/Decls.hs sed -i "s/errror/error/g" ghc/compiler/GHC/Core/Opt/SetLevels.hs sed -i "s/everwhere/everywhere/g" ghc/compiler/GHC/Core/Opt/OccurAnal.hs sed -i "s/everytime/every time/g" ghc/compiler/GHC/Runtime/Context.hs sed -i "s/exapands/expands/g" ghc/compiler/GHC/Core/Type.hs sed -i "s/exapple/example/g" ghc/compiler/GHC/Core/Utils.hs sed -i "s/excaped/escaped/g" ghc/compiler/GHC/Tc/Utils/TcType.hs sed -i "s/execuded/executed/g" ghc/compiler/GHC/Core/Opt/CallArity.hs sed -i "s/exhausive/exhaustive/g" ghc/compiler/GHC/HsToCore/Utils.hs sed -i "s/expectd/expected/g" ghc/compiler/GHC/StgToCmm/TagCheck.hs sed -i "s/experminentation/experimentation/g" ghc/compiler/GHC/Driver/Session.hs sed -i "s/explaination/explanation/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/explantation/explanation/g" ghc/compiler/GHC/Tc/Solver/Canonical.hs sed -i "s/explicitliy/explicitly/g" ghc/compiler/GHC/Unit/Module/ModSummary.hs sed -i "s/exponenial/exponential/g" ghc/compiler/GHC/Core/Unfold.hs sed -i "s/expresion/expression/g" ghc/compiler/GHC/Tc/Gen/Splice.hs sed -i "s/expressable/expressible/g" ghc/compiler/GHC/CmmToAsm/AArch64/Ppr.hs sed -i "s/extenden/extended/g" ghc/compiler/GHC/SysTools/Ar.hs sed -i "s/extendedn/extended/g" ghc/compiler/GHC/SysTools/Ar.hs sed -i "s/extremly/extremely/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/factilities/facilities/g" ghc/compiler/GHC/HsToCore/Pmc/Ppr.hs sed -i "s/fall throughs/fallthroughs/g" ghc/compiler/GHC/CmmToC.hs sed -i "s/falliblity/fallibility/g" ghc/compiler/GHC/HsToCore/Monad.hs sed -i "s/famillies/families/g" ghc/compiler/GHC/Tc/Deriv.hs sed -i "s/filenaame/filename/g" ghc/compiler/GHC/Driver/Pipeline/Execute.hs sed -i "s/freah/fresh/g" ghc/compiler/GHC/Tc/Types/Constraint.hs sed -i "s/getthe/get the/g" ghc/compiler/GHC/Plugins.hs sed -i "s/gratuitiously/gratuitously/g" ghc/compiler/GHC/Core/Opt/Simplify/Utils.hs sed -i "s/greppable/grepable/g" ghc/compiler/GHC/Rename/Splice.hs sed -i "s/hance/hence/g" ghc/compiler/GHC/Tc/Solver/Canonical.hs sed -i "s/happend/happened/g" ghc/compiler/GHC/HsToCore/Match/Literal.hs sed -i "s/havehave/have/g" ghc/compiler/GHC/Tc/Errors.hs sed -i "s/hererogeneous/heterogeneous/g" ghc/compiler/GHC/Tc/Utils/TcType.hs sed -i "s/herterogeneous/heterogeneous/g" ghc/compiler/GHC/Tc/Gen/App.hs sed -i "s/histerical/historical/g" ghc/compiler/GHC/Cmm/CLabel.hs sed -i "s/homongeneous/homogeneous/g" ghc/compiler/GHC/Tc/Utils/Instantiate.hs sed -i "s/idential/identical/g" ghc/compiler/GHC/Tc/Gen/Export.hs sed -i "s/immediatley/immediately/g" ghc/compiler/GHC/Tc/Solver/Monad.hs sed -i "s/immensly/immensely/g" ghc/compiler/GHC/StgToCmm/TagCheck.hs sed -i "s/impedence/impedance/g" ghc/compiler/GHC/Tc/Solver.hs sed -i "s/imprompto/impromptu/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/inbetween/in between/g" ghc/compiler/GHC/Cmm/Switch.hs sed -i "s/indended/intended/g" ghc/compiler/GHC/Core/Utils.hs sed -i "s/indentifier/identifier/g" ghc/compiler/GHC/Rename/HsType.hs sed -i "s/inhabiation/inhabitation/g" ghc/compiler/GHC/HsToCore/Pmc/Solver.hs sed -i "s/inhabitated/inhabited/g" ghc/compiler/GHC/HsToCore/Pmc/Solver.hs sed -i "s/ininings/inlinings/g" ghc/compiler/GHC/Tc/Utils/Monad.hs sed -i "s/interation/interaction/g" ghc/compiler/GHC/HsToCore/Expr.hs sed -i "s/interctive/interactive/g" ghc/compiler/GHC/Runtime/Context.hs sed -i "s/interger/integer/g" ghc/compiler/GHC/Utils/Binary.hs sed -i "s/interrupte/interrupt/g" ghc/compiler/GHC/Tc/Utils/Monad.hs sed -i "s/intersting/interesting/g" ghc/compiler/GHC/Core/Opt/Exitify.hs sed -i "s/intruiging/intriguing/g" ghc/compiler/GHC/Tc/Types.hs sed -i "s/jont/join/g" ghc/compiler/GHC/Core/Opt/Simplify/Env.hs sed -i "s/labourous/laborious/g" ghc/compiler/GHC/CmmToAsm/AArch64/CodeGen.hs sed -i "s/legitimally/legitimately/g" ghc/compiler/GHC/Driver/Pipeline/Execute.hs sed -i "s/mannor/manner/g" ghc/compiler/GHC/Linker/Loader.hs sed -i "s/marshall_addr/marshal_addr/g" ghc/compiler/GHC/ByteCode/Instr.hs sed -i "s/marshall_code/marshal_code/g" ghc/compiler/GHC/StgToByteCode.hs sed -i "s/martcher/matcher/g" ghc/compiler/GHC/Tc/TyCl/PatSyn.hs sed -i "s/matavariable/metavariable/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/maximium/maximum/g" ghc/compiler/GHC/Tc/Types/Constraint.hs sed -i "s/meaining/meaning/g" ghc/compiler/GHC/Core/Make.hs sed -i "s/meantion/mention/g" ghc/compiler/GHC/Tc/Solver/Canonical.hs sed -i "s/mechansim/mechanism/g" ghc/compiler/GHC/Tc/Utils/Unify.hs sed -i "s/membershib/membership/g" ghc/compiler/GHC/Tc/TyCl/Utils.hs sed -i "s/mentiones/mentions/g" ghc/compiler/GHC/Core/Opt/Exitify.hs sed -i "s/mesages/messages/g" ghc/compiler/GHC/Tc/Solver.hs sed -i "s/migth/might/g" ghc/compiler/GHC/CmmToAsm/AArch64/Ppr.hs sed -i "s/missmatch/mismatch/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/missmatch/mismatch/g" ghc/compiler/GHC/CmmToAsm/CFG.hs sed -i "s/mutiple/multiple/g" ghc/compiler/GHC/Tc/Solver.hs sed -i "s/mutliple/multiple/g" ghc/compiler/GHC/CmmToAsm/Reg/Linear.hs sed -i "s/mutually-recursivive/mutually recursive/g" ghc/compiler/GHC/Tc/Types/Origin.hs sed -i "s/neccessary/necessary/g" ghc/compiler/GHC/Core/Opt/OccurAnal.hs sed -i "s/neccessary/necessary/g" ghc/compiler/GHC/Tc/Errors/Hole.hs sed -i "s/nececesarily/necessarily/g" ghc/compiler/GHC/Core/Opt/ConstantFold.hs sed -i "s/no-sensical/nonsensical/g" ghc/compiler/GHC/Cmm/Sink.hs sed -i "s/non-sensical/nonsensical/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/noexisting/nonexisting/g" ghc/compiler/GHC/CmmToAsm/CFG.hs sed -i "s/nondeterminismand/nondeterminism/g" ghc/compiler/GHC/Unit/Module/Env.hs sed -i "s/noteable/notable/g" ghc/compiler/GHC/StgToCmm/Env.hs sed -i "s/obained/obtained/g" ghc/compiler/GHC/Tc/Module.hs sed -i "s/occurances/occurrences/g" ghc/compiler/GHC/Core/Opt/CSE.hs sed -i "s/occurances/occurrences/g" ghc/compiler/GHC/Types/Id/Info.hs sed -i "s/occured/occurred/g" ghc/compiler/GHC/Runtime/Heap/Inspect.hs sed -i "s/occured/occurred/g" ghc/compiler/GHC/Parser/Errors/Types.hs sed -i "s/occurence/occurrence/g" ghc/compiler/GHC/Iface/Ext/Types.hs sed -i "s/occurence/occurrence/g" ghc/compiler/GHC/Core/Unfold/Make.hs sed -i "s/occurences/occurrences/g" ghc/compiler/GHC/Types/Id/Info.hs sed -i "s/occuring/occurring/g" ghc/compiler/GHC/Tc/Gen/Expr.hs sed -i "s/occuring/occurring/g" ghc/compiler/GHC/Parser/Annotation.hs sed -i "s/occurrenceds/occurrences/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/occurrs/occurs/g" ghc/compiler/GHC/Tc/Errors/Types.hs sed -i "s/ommission/omission/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/oppertunity/opportunity/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/orthogal/orthogonal/g" ghc/compiler/GHC/HsToCore/Pmc/Solver.hs sed -i "s/outweighted/outweighed/g" ghc/compiler/GHC/HsToCore/Expr.hs sed -i "s/overal/overall/g" ghc/compiler/GHC/Driver/Make.hs sed -i "s/overlpapped/overlapped/g" ghc/compiler/GHC/Core/FamInstEnv.hs sed -i "s/overriden/overridden/g" ghc/compiler/GHC/Core/InstEnv.hs sed -i "s/pached/patched/g" ghc/compiler/GHC/CmmToAsm/Reg/Linear.hs sed -i "s/panicing/panicking/g" ghc/compiler/GHC/Unit/State.hs sed -i "s/panicing/panicking/g" ghc/compiler/GHC/CmmToLlvm/CodeGen.hs sed -i "s/paramaterized/parameterized/g" ghc/compiler/GHC/Tc/Gen/Foreign.hs sed -i "s/paramaters/parameters/g" ghc/compiler/GHC/Tc/Module.hs sed -i "s/parametrised/parameterised/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/parametrized/parameterized/g" ghc/compiler/GHC/Rename/Pat.hs sed -i "s/parametrized/parameterized/g" ghc/compiler/GHC/Hs/Binds.hs sed -i "s/parametrized/parameterized/g" ghc/compiler/GHC/Core/Type.hs sed -i "s/parametrized/parameterized/g" ghc/compiler/GHC/Parser/PostProcess.hs sed -i "s/parenthehsized/parenthesized/g" ghc/compiler/GHC/Parser.y sed -i "s/parralelism/parallelism/g" ghc/compiler/GHC/Unit/Env.hs sed -i "s/parrelism/parallelism/g" ghc/compiler/GHC/Driver/Pipeline.hs sed -i "s/parrelism/parallelism/g" ghc/compiler/GHC/Driver/Make.hs sed -i "s/partiall/partially/g" ghc/compiler/GHC/Driver/Pipeline/Execute.hs sed -i "s/particularlly/particularly/g" ghc/compiler/GHC/Core/Unfold/Make.hs sed -i "s/partioned/partitioned/g" ghc/compiler/GHC/Core/Opt/FloatOut.hs sed -i "s/passs/pass/g" ghc/compiler/Language/Haskell/Syntax/Type.hs sed -i "s/pendantic/pedantic/g" ghc/compiler/GHC/Core/Opt/Arity.hs sed -i "s/pendantic/pedantic/g" ghc/compiler/GHC/Types/Demand.hs sed -i "s/percision/precision/g" ghc/compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs sed -i "s/perhas/perhaps/g" ghc/compiler/GHC/Tc/Errors/Types.hs sed -i "s/persistant/persistent/g" ghc/compiler/GHC/Driver/Pipeline/Execute.hs sed -i "s/pointeds/pointed ones/g" ghc/compiler/GHC/Runtime/Heap/Inspect.hs sed -i "s/poitner/pointer/g" ghc/compiler/GHC/CmmToAsm/AArch64/Instr.hs sed -i "s/poitns/points/g" ghc/compiler/GHC/CmmToAsm/AArch64/Instr.hs sed -i "s/posiblities/possibilities/g" ghc/compiler/GHC/CmmToAsm/Reg/Graph/Base.hs sed -i "s/possibilites/possibilities/g" ghc/compiler/GHC/Utils/Misc.hs sed -i "s/possiblity/possibility/g" ghc/compiler/GHC/Core/Opt/OccurAnal.hs sed -i "s/posssibility/possibility/g" ghc/compiler/GHC/Types/Id/Make.hs sed -i "s/preceed/precede/g" ghc/compiler/GHC/Hs/Expr.hs sed -i "s/predidiction/prediction/g" ghc/compiler/GHC/CmmToAsm/X86/CodeGen.hs sed -i "s/pre-emptively/preemptively/g" ghc/compiler/GHC/HsToCore/Binds.hs sed -i "s/princial/principal/g" ghc/compiler/GHC/Tc/Types/Constraint.hs sed -i "s/principile/principle/g" ghc/compiler/GHC/Tc/Gen/Head.hs sed -i "s/princple/principle/g" ghc/compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs sed -i "s/propate/propagate/g" ghc/compiler/GHC/Core/Opt/CSE.hs sed -i "s/propoagate/propagate/g" ghc/compiler/GHC/Types/Literal.hs sed -i "s/provenenance/provenance/g" ghc/compiler/GHC/StgToCmm/Utils.hs sed -i "s/quantifed/quantified/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/quantifer/quantifier/g" ghc/compiler/Language/Haskell/Syntax/Type.hs sed -i "s/quantifer/quantifier/g" ghc/compiler/GHC/Tc/TyCl/Instance.hs sed -i "s/quantifiation/quantification/g" ghc/compiler/Language/Haskell/Syntax/Type.hs sed -i "s/quantiify/quantify/g" ghc/compiler/GHC/Tc/TyCl/PatSyn.hs sed -i "s/raather/rather/g" ghc/compiler/GHC/Tc/Gen/Sig.hs sed -i "s/raisins/reasons/g" ghc/compiler/GHC/Cmm/CLabel.hs sed -i "s/reallly/really/g" ghc/compiler/GHC/Core/Subst.hs sed -i "s/rearrangment/rearrangement/g" ghc/compiler/GHC/Rename/HsType.hs sed -i "s/recognizeable/recognizable/g" ghc/compiler/GHC/Core/Opt/Exitify.hs sed -i "s/recomoputing/recomputing/g" ghc/compiler/GHC/Core/TyCo/Rep.hs sed -i "s/recopilate/collect/g" ghc/compiler/GHC/Runtime/Debugger.hs sed -i "s/recrusive/recursive/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/recursivenss/recursiveness/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/refinementment/refinement/g" ghc/compiler/GHC/HsToCore/Pmc/Solver.hs sed -i "s/reinvinting/reinventing/g" ghc/compiler/GHC/CmmToAsm/CFG/Dominators.hs sed -i "s/rememeber/remember/g" ghc/compiler/GHC/Types/Unique/Supply.hs sed -i "s/remoselessly/remorselessly/g" ghc/compiler/GHC/Tc/Utils/TcType.hs sed -i "s/renameer/renamer/g" ghc/compiler/Language/Haskell/Syntax/Decls.hs sed -i "s/representaion/representation/g" ghc/compiler/GHC/Types/Literal.hs sed -i "s/representions/representations/g" ghc/compiler/GHC/Tc/Instance/Typeable.hs sed -i "s/residiual/residual/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/rewrtiting/rewriting/g" ghc/compiler/GHC/Cmm/Dataflow.hs sed -i "s/rigourous/rigorous/g" ghc/compiler/GHC/Stg/InferTags.hs sed -i "s/santisation/sanitisation/g" ghc/compiler/GHC/CmmToC.hs sed -i "s/santize/sanitize/g" ghc/compiler/GHC/CmmToAsm/PPC/CodeGen.hs sed -i "s/satsifies/satisfies/g" ghc/compiler/GHC/Tc/Gen/Export.hs sed -i "s/satsify/satisfy/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/sayd/says/g" ghc/compiler/GHC/Core/Opt/WorkWrap.hs sed -i "s/scrutinze/scrutinize/g" ghc/compiler/GHC/Stg/InferTags.hs sed -i "s/scrutises/scrutinises/g" ghc/compiler/GHC/Core/Opt/Simplify/Utils.hs sed -i "s/scrutises/scrutinises/g" ghc/compiler/GHC/Core/Make.hs sed -i "s/seeem/seem/g" ghc/compiler/GHC/CmmToAsm/CFG.hs sed -i "s/seens/seen/g" ghc/compiler/GHC/Core/FamInstEnv.hs sed -i "s/seeparate/separate/g" ghc/compiler/GHC/Tc/Utils/TcType.hs sed -i "s/segements/segments/g" ghc/compiler/GHC/Rename/Expr.hs sed -i "s/semphore/semaphore/g" ghc/compiler/GHC/Driver/Make.hs sed -i "s/sepearately/separately/g" ghc/compiler/GHC/Tc/TyCl.hs sed -i "s/sepperate/separate/g" ghc/compiler/GHC/Types/SafeHaskell.hs sed -i "s/serializeable/serializable/g" ghc/compiler/GHC/Iface/Recomp/Binary.hs sed -i "s/sesssion/session/g" ghc/compiler/GHC/Plugins.hs sed -i "s/sideffected/sideeffected/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/sigature/signature/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/simmpler/simpler/g" ghc/compiler/GHC/Rename/Module.hs sed -i "s/simplications/simplifications/g" ghc/compiler/GHC/Core/Opt/ConstantFold.hs sed -i "s/simplier/simplifier/g" ghc/compiler/GHC/Core/Opt/Pipeline.hs sed -i "s/singature/signature/g" ghc/compiler/GHC/Tc/TyCl/Instance.hs sed -i "s/slighty/slightly/g" ghc/compiler/GHC/Tc/Solver/Canonical.hs sed -i "s/sligthtly/slightly/g" ghc/compiler/GHC/Core/Opt/Simplify/Utils.hs sed -i "s/specialiations/specialisations/g" ghc/compiler/GHC/Core/Opt/WorkWrap.hs sed -i "s/specifiec/specified/g" ghc/compiler/GHC/ByteCode/Instr.hs sed -i "s/speicfied/specified/g" ghc/compiler/GHC/Tc/Gen/Bind.hs sed -i "s/standalane/standalone/g" ghc/compiler/GHC/Tc/Gen/HsType.hs sed -i "s/statisfy/satisfy/g" ghc/compiler/GHC/HsToCore/Pmc/Solver.hs sed -i "s/staturated/saturated/g" ghc/compiler/GHC/Core/Coercion.hs sed -i "s/ stil / still /g" ghc/compiler/GHC/CmmToAsm/BlockLayout.hs sed -i "s/straghtforward/straightforward/g" ghc/compiler/GHC/Parser/PostProcess/Haddock.hs sed -i "s/stratightforard/straightforward/g" ghc/compiler/GHC/Tc/Solver.hs sed -i "s/strengten/strengthen/g" ghc/compiler/GHC/Tc/Solver/InertSet.hs sed -i "s/stricness/strictness/g" ghc/compiler/GHC/Iface/Tidy.hs sed -i "s/stricness/strictness/g" ghc/compiler/GHC/Core/Opt/DmdAnal.hs sed -i "s/stricness/strictness/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/striped/stripped/g" ghc/compiler/GHC/Driver/Main.hs sed -i "s/subsitution/substitution/g" ghc/compiler/GHC/Core/Opt/WorkWrap/Utils.hs sed -i "s/substitition/substitution/g" ghc/compiler/GHC/Core/Lint.hs sed -i "s/substittion/substitution/g" ghc/compiler/GHC/Core/Lint.hs sed -i "s/substituion/substitution/g" ghc/compiler/GHC/Core/RoughMap.hs sed -i "s/superceeds/supersedes/g" ghc/compiler/GHC/CmmToAsm/CFG.hs sed -i "s/suppors/supports/g" ghc/compiler/GHC/Utils/Logger.hs sed -i "s/supppose/suppose/g" ghc/compiler/GHC/Tc/Utils/Unify.hs sed -i "s/suppressable/suppressible/g" ghc/compiler/GHC/Driver/Session.hs sed -i "s/synomym/synonym/g" ghc/compiler/GHC/Tc/TyCl/Class.hs sed -i "s/synomyms/synonyms/g" ghc/compiler/GHC/Core/Opt/Simplify/Env.hs sed -i "s/thats/that's/g" ghc/compiler/GHC/Cmm/ContFlowOpt.hs sed -i "s/themp/them/g" ghc/compiler/Language/Haskell/Syntax/Expr.hs sed -i "s/theres/there's/g" ghc/compiler/GHC/Data/Graph/Color.hs sed -i "s/theses/these/g" ghc/compiler/GHC/SysTools/Elf.hs sed -i "s/togethed/together/g" ghc/compiler/GHC/Driver/Env/KnotVars.hs sed -i "s/transfomer/transformer/g" ghc/compiler/GHC/Types/Demand.hs sed -i "s/transformtions/transformations/g" ghc/compiler/GHC/Core/Opt/simplifier.tib sed -i "s/ubound/unbound/g" ghc/compiler/GHC/Rename/Fixity.hs sed -i "s/underlyind/underlying/g" ghc/compiler/GHC/HsToCore/Pmc/Solver.hs sed -i "s/undersatured/undersaturated/g" ghc/compiler/GHC/Stg/InferTags/Rewrite.hs sed -i "s/uneccessary/unecessary/g" ghc/compiler/GHC/Tc/Errors/Hole.hs sed -i "s/unificatdion/unification/g" ghc/compiler/GHC/Tc/TyCl/PatSyn.hs sed -i "s/uninhabitated/uninhabited/g" ghc/compiler/GHC/HsToCore/Pmc/Desugar.hs sed -i "s/uniquesc/uniques/g" ghc/compiler/GHC/Builtin/Uniques.hs sed -i "s/unnecesasry/unnecessary/g" ghc/compiler/GHC/Linker/MacOS.hs sed -i "s/usuage/usage/g" ghc/compiler/GHC/Stg/Debug.hs sed -i "s/variablas/variables/g" ghc/compiler/GHC/Cmm/Liveness.hs sed -i "s/varialbe/variable/g" ghc/compiler/GHC/Tc/Gen/App.hs sed -i "s/varibles/variables/g" ghc/compiler/GHC/Tc/Utils/TcMType.hs sed -i "s/varibles/variables/g" ghc/compiler/GHC/Tc/Gen/App.hs sed -i "s/visibile/visible/g" ghc/compiler/GHC/Tc/Validity.hs sed -i "s/visiblity/visibility/g" ghc/compiler/GHC/Tc/Solver/Interact.hs sed -i "s/wapper/wrapper/g" ghc/compiler/GHC/Core/DataCon.hs sed -i "s/wappings/wrappings/g" ghc/compiler/GHC/HsToCore/Utils.hs sed -i "s/wavey/wavy/g" ghc/compiler/GHC/Core/Type.hs sed -i "s/whan/when/g" ghc/compiler/GHC/Parser/Lexer.x sed -i "s/ wnen / when /g" ghc/compiler/GHC/Core.hs sed -i "s/whodunnit/whodunit/g" ghc/compiler/GHC/Stg/Pipeline.hs sed -i "s/work-hourse/workhorse/g" ghc/compiler/GHC/Core/Opt/CallArity.hs $
192 files changed, 399 insertions(+), 399 deletions(-)
as the spelling of
whodunnit
was changed in compiler/GHC/Stg/Pipeline.hsan additional commit was made to change the spelling of
whodunnit
in compiler/GHC/Stg/Lint.hs$ cat typo.sh #!/bin/sh sed -i "s/whodunnit/whodunit/g" ghc/compiler/GHC/Stg/Lint.hs $
1 file changed, 2 insertions(+), 2 deletions(-)
- Ghost User changed the description
Compare with previous version changed the description
- Ghost User mentioned in merge request !8720 (closed)
mentioned in merge request !8720 (closed)
- Ghost User mentioned in merge request !8721 (closed)
mentioned in merge request !8721 (closed)
- Author Contributor
should have rebased Eric Lindblad / GHC before creating the new branch
may revisit these files in another MR, e.g. "various typo fixes"
compiler/GHC/Core/Opt/DmdAnal.hs
should line 1965 be edited
$ grep -n both\'d ghc/compiler/GHC/Core/Opt/DmdAnal.hs 1965: -- L demand doesn't get both'd with the Bot coming up from the inner $
compiler/GHC/Parser/Annotation.hs
this is awkward
$ perl -ne 'print if $. == 649 .. 650' ghc/compiler/GHC/Parser/Annotation.hs -- | Annotation for items appearing in a list. They can have one or -- more trailing punctuations items, such as commas or semicolons. $
compiler/GHC/Core/Rules.hs
compiler/GHC/Stg/Lint.hs
compiler/GHC/CoreToStg/Prep.hs
compiler/GHC/Core/Opt/Specialise.hs
compiler/GHC/ByteCode/Instr.hs
compiler/GHC/StgToByteCode.hs# sed -i "s/agressively/aggressively/g" ghc/compiler/GHC/Core/Rules.hs # sed -i "s/beteen/between/g" ghc/compiler/GHC/Stg/Lint.hs # sed -i "s/beucase/because/g" ghc/compiler/GHC/CoreToStg/Prep.hs # sed -i "s/invaidate/invalidate/g" ghc/compiler/GHC/Core/Opt/Specialise.hs # sed -i "s/marshall /marshal /g" ghc/compiler/GHC/ByteCode/Instr.hs # sed -i "s/marshall /marshal /g" ghc/compiler/GHC/StgToByteCode.hs # sed -i "s/missmatched/mismatched/g" ghc/compiler/GHC/Stg/Lint.hs # sed -i "s/reflextve/reflexive/g" ghc/compiler/GHC/Core/Rules.hs # sed -i "s/seee//g" ghc/compiler/GHC/Core/Rules.hs # sed -i "s/specialision/specialisation/g" ghc/compiler/GHC/Core/Opt/Specialise.hs # sed -i "s/tranformations/transformations/g" ghc/compiler/GHC/CoreToStg/Prep.hs # sed -i "s/varibles/variables/g" ghc/compiler/GHC/CoreToStg/Prep.hs
also there's the unattended to typo fix omitted from
!8659 (closed)
# sed -i "s/wastefull/wasteful/g" ghc/libraries/base/GHC/Event/Windows.hsc
- Author Contributor
pipelines failing on the merge request
most of the changes affect comments or messages
actual code modification appears in these files (over 2 commits)
compiler/GHC/ByteCode/Instr.hs
compiler/GHC/Stg/Lint.hs
compiler/GHC/Stg/Pipeline.hs
compiler/GHC/Utils/Misc.hshttps://gitlab.haskell.org/lindblad/ghc/-/commit/a2410309a84a58557639f5ffc2cbec9e77be139b.patch
diff --git a/compiler/GHC/ByteCode/Instr.hs b/compiler/GHC/ByteCode/Instr.hs index ebbce3ef502..755d4f49bfa 100644 --- a/compiler/GHC/ByteCode/Instr.hs +++ b/compiler/GHC/ByteCode/Instr.hs @@ -68,12 +68,12 @@ data BCInstr | PUSH16 !Word16 | PUSH32 !Word16 - -- Push the specifiec local as a 8, 16, 32 bit value onto the stack, but the + -- Push the specified local as a 8, 16, 32 bit value onto the stack, but the -- value will take the whole word on the stack (i.e., the stack will grow by -- a word) -- This is useful when extracting a packed constructor field for further use. -- Currently we expect all values on the stack to take full words, except for - -- the ones used for PACK (i.e., actually constracting new data types, in + -- the ones used for PACK (i.e., actually constructing new data types, in -- which case we use PUSH{8,16,32}) | PUSH8_W !Word16 | PUSH16_W !Word16 @@ -299,9 +299,9 @@ instance Outputable BCInstr where ppr (TESTEQ_P i lab) = text "TESTEQ_P" <+> ppr i <+> text "__" <> ppr lab ppr CASEFAIL = text "CASEFAIL" ppr (JMP lab) = text "JMP" <+> ppr lab - ppr (CCALL off marshall_addr flags) = text "CCALL " <+> ppr off + ppr (CCALL off marshal_addr flags) = text "CCALL " <+> ppr off <+> text "marshall code at" - <+> text (show marshall_addr) + <+> text (show marshal_addr) <+> (case flags of 0x1 -> text "(interruptible)" 0x2 -> text "(unsafe)"
diff --git a/compiler/GHC/Stg/Pipeline.hs b/compiler/GHC/Stg/Pipeline.hs index c5f7bc2da3b..b35d564606c 100644 --- a/compiler/GHC/Stg/Pipeline.hs +++ b/compiler/GHC/Stg/Pipeline.hs @@ -96,7 +96,7 @@ stg2stg logger extra_vars opts this_mod binds diag_opts ppr_opts extra_vars this_mod unarised | otherwise - = \ _whodunnit _binds -> return () + = \ _whodunit _binds -> return () ------------------------------------------- do_stg_pass :: Module -> [StgTopBinding] -> StgToDo -> StgM [StgTopBinding]
diff --git a/compiler/GHC/Utils/Misc.hs b/compiler/GHC/Utils/Misc.hs index 986d95144e8..6c7c64cf6ad 100644 --- a/compiler/GHC/Utils/Misc.hs +++ b/compiler/GHC/Utils/Misc.hs @@ -971,10 +971,10 @@ fuzzyMatch key vals = fuzzyLookup key [(v,v) | v <- vals] -- | Search for possible matches to the users input in the given list, -- returning a small number of ranked results fuzzyLookup :: String -> [(String,a)] -> [a] -fuzzyLookup user_entered possibilites +fuzzyLookup user_entered possibilities = map fst $ take mAX_RESULTS $ List.sortBy (comparing snd) [ (poss_val, sort_key) - | (poss_str, poss_val) <- possibilites + | (poss_str, poss_val) <- possibilities , let distance = restrictedDamerauLevenshteinDistance poss_str user_entered , distance <= fuzzy_threshold , let sort_key = (distance, length poss_str, poss_str)
https://gitlab.haskell.org/lindblad/ghc/-/commit/9d7471f8f127f6862adf3d7d3345805bd382abb7.patch
diff --git a/compiler/GHC/Stg/Lint.hs b/compiler/GHC/Stg/Lint.hs index 15586cfce9c..8ca8ef95c62 100644 --- a/compiler/GHC/Stg/Lint.hs +++ b/compiler/GHC/Stg/Lint.hs @@ -134,7 +134,7 @@ lintStgTopBindings :: forall a . (OutputablePass a, BinderP a ~ Id) -> [GenStgTopBinding a] -> IO () -lintStgTopBindings platform logger diag_opts opts extra_vars this_mod unarised whodunnit binds +lintStgTopBindings platform logger diag_opts opts extra_vars this_mod unarised whodunit binds = {-# SCC "StgLint" #-} case initL platform diag_opts this_mod unarised opts top_level_binds (lint_binds binds) of Nothing -> @@ -143,7 +143,7 @@ lintStgTopBindings platform logger diag_opts opts extra_vars this_mod unarised w logMsg logger Err.MCDump noSrcSpan $ withPprStyle defaultDumpStyle (vcat [ text "*** Stg Lint ErrMsgs: in" <+> - text whodunnit <+> text "***", + text whodunit <+> text "***", msg, text "*** Offending Program ***", pprGenStgTopBindings opts binds,
- Author Contributor
should have posted this before
doesn't allocate for sed string with spaces
$ cat typos.pl #!/usr/bin/env perl use strict; use warnings; use autodie; my $fh; my $file = 'typos'; open $fh, '<', $file; while ( my $line = <$fh> ) { my @typo = split '/', $line; my @path = split ' ', $line; print "grep -n $typo[1] $path[3]\n"; } close $fh; $
example use
$ perl -ne 'print if $. eq 3 .. 6' typos.sh > typos $ ./typos.pl grep -n Accessessors ghc/compiler/GHC/Settings.hs grep -n Accessessors ghc/compiler/GHC/Driver/Session.hs grep -n Acumulating ghc/compiler/GHC/Core/TyCo/FVs.hs grep -n Analsysis ghc/compiler/GHC/Core/Opt/DmdAnal.hs $
the output of
typos.pl
of course can be redirected to a file - Author Contributor
evidently MOVEABLE is the spelling used for Windows' resource files
of consequence this change was causing CI to fail
sed -i "s/MOVEABLE/MOVABLE/g" ghc/compiler/GHC/Linker/Windows.hs
the sed command has been removed from typos.sh
compiler/GHC/Linker/Windows.hs should not have been edited in the initial commit
- Ghost User mentioned in commit ffe49f19
mentioned in commit ffe49f19
- Ghost User mentioned in commit 646d15ad
mentioned in commit 646d15ad