Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Alfredo Di Napoli
GHC
Commits
6ac8a72f
Commit
6ac8a72f
authored
Jun 18, 2018
by
Gabor Greif
💬
Browse files
Typofixes in docs and comments [ci skip]
parent
30b029be
Changes
24
Hide whitespace changes
Inline
Side-by-side
compiler/basicTypes/MkId.hs
View file @
6ac8a72f
...
...
@@ -124,7 +124,7 @@ Note [magicIds]
~~~~~~~~~~~~~~~
The magicIds
* Are expo
t
ted from GHC.Maic
* Are expo
r
ted from GHC.Maic
* Can be defined in Haskell (and are, in ghc-prim:GHC/Magic.hs).
This definition at least generates Haddock documentation for them.
...
...
compiler/coreSyn/CoreLint.hs
View file @
6ac8a72f
...
...
@@ -1384,7 +1384,7 @@ Consider (Trac #14939)
f :: forall (cls :: * -> Constraint) (b :: Alg cls *). b
Here 'cls' appears free in b's kind, which would usually be illegal
(bec
u
ase in (forall a. ty), ty's kind should not mention 'a'). But
(beca
u
se in (forall a. ty), ty's kind should not mention 'a'). But
#in this case (Alg cls *) = *, so all is well. Currently we allow
this, and make Lint expand synonyms where necessary to make it so.
...
...
compiler/coreSyn/CoreSyn.hs
View file @
6ac8a72f
...
...
@@ -757,7 +757,7 @@ transformation universally. This transformation would do:
but that is ill-typed, as `x` is type `a`, not `Bool`.
This
is
also justifies why we do not consider the `e` in `e |> co` to be in
This also justifies why we do not consider the `e` in `e |> co` to be in
tail position: A cast changes the type, but the type must be the same. But
operationally, casts are vacuous, so this is a bit unfortunate! See #14610 for
ideas how to fix this.
...
...
compiler/iface/BinIface.hs
View file @
6ac8a72f
...
...
@@ -208,7 +208,7 @@ putWithUserData log_action bh payload = do
-- Remember where the symbol table pointer will go
symtab_p_p
<-
tellBin
bh
put_
bh
symtab_p_p
-- Make some intial state
-- Make some in
i
tial state
symtab_next
<-
newFastMutInt
writeFastMutInt
symtab_next
0
symtab_map
<-
newIORef
emptyUFM
...
...
compiler/main/DynFlags.hs
View file @
6ac8a72f
...
...
@@ -880,7 +880,7 @@ data DynFlags = DynFlags {
floatLamArgs
::
Maybe
Int
,
-- ^ Arg count for lambda floating
-- See CoreMonad.FloatOutSwitches
cmmProcAlignment
::
Maybe
Int
,
-- ^ Align Cmm functions at this boundry or use default.
cmmProcAlignment
::
Maybe
Int
,
-- ^ Align Cmm functions at this bound
a
ry or use default.
historySize
::
Int
,
-- ^ Simplification history size
...
...
compiler/main/TidyPgm.hs
View file @
6ac8a72f
...
...
@@ -612,7 +612,7 @@ chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_
where
nc_var
=
hsc_NC
hsc_env
-- init_ext_ids is the intial list of Ids that should be
-- init_ext_ids is the in
i
tial list of Ids that should be
-- externalised. It serves as the starting point for finding a
-- deterministic, tidy, renaming for all external Ids in this
-- module.
...
...
compiler/rename/RnSource.hs
View file @
6ac8a72f
...
...
@@ -392,7 +392,7 @@ rnHsForeignDecl (XForeignDecl _) = panic "rnHsForeignDecl"
-- | For Windows DLLs we need to know what packages imported symbols are from
-- to generate correct calls. Imported symbols are tagged with the current
-- package, so if they get inlined across a package boundry we'll still
-- package, so if they get inlined across a package bound
a
ry we'll still
-- know where they're from.
--
patchForeignImport
::
UnitId
->
ForeignImport
->
ForeignImport
...
...
compiler/simplCore/SimplUtils.hs
View file @
6ac8a72f
...
...
@@ -1088,7 +1088,7 @@ spectral/mandel/Mandel.hs, where the mandelset function gets a useful
let-float if you inline windowToViewport
However, as usual for Gentle mode, do not inline things that are
inactive in the intial stages. See Note [Gentle mode].
inactive in the in
i
tial stages. See Note [Gentle mode].
Note [Stable unfoldings and preInlineUnconditionally]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
...
...
@@ -2231,7 +2231,7 @@ mkCase3 _dflags scrut bndr alts_ty alts
=
return
(
Case
scrut
bndr
alts_ty
alts
)
-- See Note [Exitification] and Note [Do not inline exit join points] in Exitify.hs
-- This lives here (and not in Id) bec
u
ase occurrence info is only valid on
-- This lives here (and not in Id) beca
u
se occurrence info is only valid on
-- InIds, so it's crucial that isExitJoinId is only called on freshly
-- occ-analysed code. It's not a generic function you can call anywhere.
isExitJoinId
::
Var
->
Bool
...
...
compiler/specialise/Rules.hs
View file @
6ac8a72f
...
...
@@ -678,7 +678,7 @@ obscure way in Trac #14777. Problem was that during matching we look
up target-term variables in the in-scope set (see Note [Lookup
in-scope]). If a target-term variable happens to name-clash with a
template variable, that lookup will find the template variable, which
is /utt
t
erly/ bogus. In Trac #14777, this transformed a term variable
is /utterly/ bogus. In Trac #14777, this transformed a term variable
into a type variable, and then crashed when we wanted its idInfo.
------ End of historical note -------
...
...
compiler/typecheck/TcDerivInfer.hs
View file @
6ac8a72f
...
...
@@ -398,7 +398,7 @@ We have some special hacks to support things like
data T = MkT Int# deriving ( Show )
Specifically, we use TcGenDeriv.box to box the Int# into an Int
(which we know how to show), and append a '#'. Parenthes
i
s are not required
(which we know how to show), and append a '#'. Parenthes
e
s are not required
for unboxed values (`MkT -3#` is a valid expression).
Note [Superclasses of derived instance]
...
...
compiler/typecheck/TcExpr.hs
View file @
6ac8a72f
...
...
@@ -1103,7 +1103,7 @@ data HsArg tm ty
{-
Note [HsArgPar]
A HsArgPar indicates that everything to the left of this in the argument list is
enclosed in parenthes
i
s together with the function itself. It is necessary so
enclosed in parenthes
e
s together with the function itself. It is necessary so
that we can recreate the parenthesis structure in the original source after
typechecking the arguments.
...
...
compiler/typecheck/TcHsType.hs
View file @
6ac8a72f
...
...
@@ -588,7 +588,7 @@ tc_infer_hs_type mode (HsOpTy _ lhs lhs_op@(L _ hs_op) rhs)
tc_infer_hs_type
mode
(
HsKindSig
_
ty
sig
)
=
do
{
sig'
<-
tcLHsKindSig
KindSigCtxt
sig
-- We must typec
k
eck the kind signature, and solve all
-- We must typec
h
eck the kind signature, and solve all
-- its equalities etc; from this point on we may do
-- things like instantiate its foralls, so it needs
-- to be fully determined (Trac #149904)
...
...
compiler/typecheck/TcRnTypes.hs
View file @
6ac8a72f
...
...
@@ -1763,7 +1763,7 @@ Example 1: (c Int), where c :: * -> Constraint. We can't do anything
Example 2: a ~ b, where a :: *, b :: k, where k is a kind variable
We don't want to use this to substitute 'b' for 'a', in case
'k' is subequently unifed with (say) *->*, because then
'k' is sub
s
equently unifed with (say) *->*, because then
we'd have ill-kinded types floating about. Rather we want
to defer using the equality altogether until 'k' get resolved.
...
...
compiler/typecheck/TcSimplify.hs
View file @
6ac8a72f
...
...
@@ -893,7 +893,7 @@ decideQuantification infer_mode rhs_tclvl name_taus psigs candidates
;
psig_theta
<-
TcM
.
zonkTcTypes
(
concatMap
sig_inst_theta
psigs
)
;
let
quantifiable_candidates
=
pickQuantifiablePreds
(
mkVarSet
qtvs
)
candidates
-- NB: do /not/ run pickQuantifi
e
ablePreds over psig_theta,
-- NB: do /not/ run pickQuantifiablePreds over psig_theta,
-- because we always want to quantify over psig_theta, and not
-- drop any of them; e.g. CallStack constraints. c.f Trac #14658
...
...
compiler/typecheck/TcTyClsDecls.hs
View file @
6ac8a72f
...
...
@@ -421,7 +421,7 @@ We do the following steps:
error if B is used in any of the kinds needed to initialse
B's kind (e.g. (a :: Type)) here
- Extend the type env with these intial kinds (monomorphic for
- Extend the type env with these in
i
tial kinds (monomorphic for
decls that lack a CUSK)
B :-> TcTyCon <initial kind>
(thereby overriding the B :-> TyConPE binding)
...
...
compiler/types/TyCon.hs
View file @
6ac8a72f
...
...
@@ -2552,7 +2552,7 @@ data RecTcChecker = RC !Int (NameEnv Int)
-- we have encountered each TyCon
initRecTc
::
RecTcChecker
-- Intialise with a fixed max bound of 100
-- In
i
tialise with a fixed max bound of 100
-- We should probably have a flag for this
initRecTc
=
RC
100
emptyNameEnv
...
...
compiler/types/Unify.hs
View file @
6ac8a72f
...
...
@@ -595,7 +595,7 @@ So, we work as follows:
[ b :: *, z :: a, rest :: G a z ]
6. Apply the substitution left-to-right to the kinds of these
tyvars, extendin
n
g it each time with a new binding, so we
tyvars, extending it each time with a new binding, so we
finish up with
[ xs :-> ..as before..
, a :-> ..as before..
...
...
@@ -604,10 +604,10 @@ So, we work as follows:
, rest :-> rest :: G a (z :: b) ]
Note that rest now has the right kind
7. Apply this extended substution (once) to the range of
the /original/ substituion. (Note that we do the
7. Apply this extended subst
it
ution (once) to the range of
the /original/ substitu
t
ion. (Note that we do the
extended substitution would go on forever if you tried
to find its fixpoint, bec
u
ase it maps z to z.)
to find its fixpoint, beca
u
se it maps z to z.)
8. And go back to step 1
...
...
docs/users_guide/debug-info.rst
View file @
6ac8a72f
...
...
@@ -9,7 +9,7 @@ useable by most UNIX debugging tools.
-g⟨n⟩
:shortdesc: Produce DWARF debug information in compiled object files.
⟨n⟩ can be 0, 1, or 2, with higher numbers producing richer
output. If ⟨n⟩ is omitted level 2 is assumed.
output. If ⟨n⟩ is omitted
,
level 2 is assumed.
:type: dynamic
:category: debugging
...
...
@@ -18,7 +18,7 @@ useable by most UNIX debugging tools.
Emit debug information in object code. Currently only DWARF debug
information is supported on x86-64 and i386. Currently debug levels 0
through 3 are accepted, with 0 disabling debug information production
and higher numbers producing richer output. If ⟨n⟩ is omitted level 2
and higher numbers producing richer output. If ⟨n⟩ is omitted
,
level 2
is assumed.
...
...
docs/users_guide/debugging.rst
View file @
6ac8a72f
...
...
@@ -384,7 +384,7 @@ These flags dump various phases of GHC's C-\\- pipeline.
file parsing.
Cmm dumps don't include unreachable blocks since we print
blocks in reverse post
order.
blocks in reverse post
-
order.
.. ghc-flag:: -ddump-cmm-from-stg
:shortdesc: Dump STG-to-C-\\- output
...
...
@@ -763,7 +763,7 @@ Checking for consistency
useful when finding pointer tagging issues.
.. ghc-flag:: -fproc-alignment
:shortdesc: Align functions at given boundry.
:shortdesc: Align functions at given bound
a
ry.
:type: dynamic
Align functions to multiples of the given value. Only valid values are powers
...
...
docs/users_guide/extending_ghc.rst
View file @
6ac8a72f
...
...
@@ -605,7 +605,7 @@ to segfaults or other runtime misbehaviour.
Source
plugins
~~~~~~~~~~~~~~
In
addition
al
to
core
and
type
checker
plugins
,
you
can
install
plugins
that
can
In
addition
to
core
and
type
checker
plugins
,
you
can
install
plugins
that
can
access
different
representations
of
the
source
code
.
The
main
purpose
of
these
plugins
is
to
make
it
easier
to
implement
development
tools
.
...
...
Prev
1
2
Next
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment