Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Glasgow Haskell Compiler
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
0
Issues
0
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
0
Merge Requests
0
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Packages & Registries
Packages & Registries
Package Registry
Container Registry
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Shayne Fletcher
Glasgow Haskell Compiler
Commits
9005f91e
Commit
9005f91e
authored
Jan 26, 2014
by
Gabor Greif
💬
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Squash some spelling issues
parent
5281dd6f
Changes
22
Hide whitespace changes
Inline
Side-by-side
Showing
22 changed files
with
30 additions
and
30 deletions
+30
-30
compiler/basicTypes/BasicTypes.lhs
compiler/basicTypes/BasicTypes.lhs
+1
-1
compiler/cmm/CmmContFlowOpt.hs
compiler/cmm/CmmContFlowOpt.hs
+1
-1
compiler/coreSyn/CoreLint.lhs
compiler/coreSyn/CoreLint.lhs
+1
-1
compiler/coreSyn/CoreSubst.lhs
compiler/coreSyn/CoreSubst.lhs
+2
-2
compiler/coreSyn/CoreSyn.lhs
compiler/coreSyn/CoreSyn.lhs
+1
-1
compiler/hsSyn/HsUtils.lhs
compiler/hsSyn/HsUtils.lhs
+1
-1
compiler/rename/RnEnv.lhs
compiler/rename/RnEnv.lhs
+2
-2
compiler/rename/RnPat.lhs
compiler/rename/RnPat.lhs
+2
-2
compiler/rename/RnSource.lhs
compiler/rename/RnSource.lhs
+1
-1
compiler/simplCore/OccurAnal.lhs
compiler/simplCore/OccurAnal.lhs
+3
-3
compiler/simplCore/SimplCore.lhs
compiler/simplCore/SimplCore.lhs
+1
-1
compiler/stgSyn/CoreToStg.lhs
compiler/stgSyn/CoreToStg.lhs
+1
-1
compiler/typecheck/TcMType.lhs
compiler/typecheck/TcMType.lhs
+1
-1
docs/comm/exts/th.html
docs/comm/exts/th.html
+1
-1
docs/comm/the-beast/basicTypes.html
docs/comm/the-beast/basicTypes.html
+1
-1
docs/comm/the-beast/renamer.html
docs/comm/the-beast/renamer.html
+1
-1
docs/comm/the-beast/simplifier.html
docs/comm/the-beast/simplifier.html
+1
-1
docs/comm/the-beast/stg.html
docs/comm/the-beast/stg.html
+2
-2
docs/comm/the-beast/typecheck.html
docs/comm/the-beast/typecheck.html
+3
-3
docs/ndp/haskell.sty
docs/ndp/haskell.sty
+1
-1
docs/ndp/vect.tex
docs/ndp/vect.tex
+1
-1
docs/users_guide/glasgow_exts.xml
docs/users_guide/glasgow_exts.xml
+1
-1
No files found.
compiler/basicTypes/BasicTypes.lhs
View file @
9005f91e
...
...
@@ -566,7 +566,7 @@ defn of OccInfo here, safely at the bottom
\begin{code}
-- | Identifier occurrence information
data OccInfo
= NoOccInfo -- ^ There are many occurrences, or unknown occurences
= NoOccInfo -- ^ There are many occurrences, or unknown occur
r
ences
| IAmDead -- ^ Marks unused variables. Sometimes useful for
-- lambda and case-bound variables.
...
...
compiler/cmm/CmmContFlowOpt.hs
View file @
9005f91e
...
...
@@ -246,7 +246,7 @@ blockConcat splitting_procs g@CmmGraph { g_entry = entry_id }
-- (3) increase number of predecessors of dest by 1
-- (4) decrease number of predecessors of b' by 1
--
-- Later we will use replaceLabels to substitute all occurences of b'
-- Later we will use replaceLabels to substitute all occur
r
ences of b'
-- with dest.
|
splitting_procs
,
Just
b'
<-
callContinuation_maybe
last
...
...
compiler/coreSyn/CoreLint.lhs
View file @
9005f91e
...
...
@@ -116,7 +116,7 @@ to the type of the binding variable. lintBinders does this.
For Ids, the type-substituted Id is added to the in_scope set (which
itself is part of the TvSubst we are carrying down), and when we
find an occurence of an Id, we fetch it from the in-scope set.
find an occur
r
ence of an Id, we fetch it from the in-scope set.
\begin{code}
...
...
compiler/coreSyn/CoreSubst.lhs
View file @
9005f91e
...
...
@@ -769,7 +769,7 @@ Note [Worker inlining]
A worker can get sustituted away entirely.
- it might be trivial
- it might simply be very small
We do not treat an InlWrapper as an 'occurrence' in the occurence
We do not treat an InlWrapper as an 'occurrence' in the occur
r
ence
analyser, so it's possible that the worker is not even in scope any more.
In all all these cases we simply drop the special case, returning to
...
...
@@ -843,7 +843,7 @@ simpleOptExpr :: CoreExpr -> CoreExpr
-- We also inline bindings that bind a Eq# box: see
-- See Note [Optimise coercion boxes agressively].
--
-- The result is NOT guaranteed occurence-analysed, because
-- The result is NOT guaranteed occur
r
ence-analysed, because
-- in (let x = y in ....) we substitute for x; so y's occ-info
-- may change radically
...
...
compiler/coreSyn/CoreSyn.lhs
View file @
9005f91e
...
...
@@ -992,7 +992,7 @@ See also Note [Inlining an InlineRule] in CoreUnfold.
Note [OccInfo in unfoldings and rules]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In unfoldings and rules, we guarantee that the template is occ-analysed,
so that the occurence info on the binders is correct. This is important,
so that the occur
r
ence info on the binders is correct. This is important,
because the Simplifier does not re-analyse the template when using it. If
the occurrence info is wrong
- We may get more simpifier iterations than necessary, because
...
...
compiler/hsSyn/HsUtils.lhs
View file @
9005f91e
...
...
@@ -701,7 +701,7 @@ hsLTyClDeclBinders :: Eq name => Located (TyClDecl name) -> [Located name]
-- ^ Returns all the /binding/ names of the decl.
-- The first one is guaranteed to be the name of the decl. For record fields
-- mentioned in multiple constructors, the SrcLoc will be from the first
-- occurence. We use the equality to filter out duplicate field names.
-- occur
r
ence. We use the equality to filter out duplicate field names.
--
-- Each returned (Located name) is wrapped in a @SrcSpan@ of the whole
-- /declaration/, not just the name itself (which is how it appears in
...
...
compiler/rename/RnEnv.lhs
View file @
9005f91e
...
...
@@ -450,7 +450,7 @@ Thus:
data G a
instance C S where
data G S = Y1 | Y2
Even though there are two G's in scope (M.G and Blib.G), the occurence
Even though there are two G's in scope (M.G and Blib.G), the occur
r
ence
of 'G' in the 'instance C S' decl is unambiguous, because C has only
one associated type called G. This is exactly what happens for methods,
and it is only consistent to do the same thing for types. That's the
...
...
@@ -611,7 +611,7 @@ When the user writes:
'Zero' in the type signature of 'foo' is parsed as:
HsTyVar ("Zero", TcClsName)
When the renamer hits this occurence of 'Zero' it's going to realise
When the renamer hits this occur
r
ence of 'Zero' it's going to realise
that it's not in scope. But because it is renaming a type, it knows
that 'Zero' might be a promoted data constructor, so it will demote
its namespace to DataName and do a second lookup.
...
...
compiler/rename/RnPat.lhs
View file @
9005f91e
...
...
@@ -153,7 +153,7 @@ Consider
g _ = T1
Arguaby we should report T2 as unused, even though it appears in a
Arguab
l
y we should report T2 as unused, even though it appears in a
pattern, because it never occurs in a constructed position. See
Trac #7336.
However, implementing this in the face of pattern synonyms would be
...
...
@@ -166,7 +166,7 @@ we need to observe the dependency between P1 and P2 so that type
checking can be done in the correct order (just like for value
bindings). Dependencies between bindings is analyzed in the renamer,
where we don't know yet whether P2 is a constructor or a pattern
synonym. So for now, we do report conid occur
a
nces in patterns as
synonym. So for now, we do report conid occur
re
nces in patterns as
uses.
%*********************************************************
...
...
compiler/rename/RnSource.lhs
View file @
9005f91e
...
...
@@ -60,7 +60,7 @@ for undefined tyvars, and tyvars in contexts that are ambiguous.
(Some of this checking has now been moved to module @TcMonoType@,
since we don't have functional dependency information at this point.)
\item
Checks that all variable occurences are defined.
Checks that all variable occur
r
ences are defined.
\item
Checks the @(..)@ etc constraints in the export list.
\end{enumerate}
...
...
compiler/simplCore/OccurAnal.lhs
View file @
9005f91e
...
...
@@ -72,7 +72,7 @@ occurAnalysePgm this_mod active_rule imp_rules vects vectVars binds
vectVars)
-- The RULES and VECTORISE declarations keep things alive! (For VECTORISE declarations,
-- we only get them *until* the vectoriser runs. Afterwards, these dependencies are
-- reflected in 'vectors' — see Note [Vectorisation declarations and occurences].)
-- reflected in 'vectors' — see Note [Vectorisation declarations and occur
r
ences].)
-- Note [Preventing loops due to imported functions rules]
imp_rules_edges = foldr (plusVarEnv_C unionVarSet) emptyVarEnv
...
...
@@ -92,7 +92,7 @@ occurAnalysePgm this_mod active_rule imp_rules vects vectVars binds
(final_usage, bind') = occAnalBind env env imp_rules_edges bind bs_usage
occurAnalyseExpr :: CoreExpr -> CoreExpr
-- Do occurrence analysis, and discard occurence info returned
-- Do occurrence analysis, and discard occur
r
ence info returned
occurAnalyseExpr = occurAnalyseExpr' True -- do binder swap
occurAnalyseExpr_NoBinderSwap :: CoreExpr -> CoreExpr
...
...
@@ -1657,7 +1657,7 @@ From the original
we will get
case x of cb(live) { p -> let x = cb in ...x... }
Core Lint never expects to find an *occurence* of an Id marked
Core Lint never expects to find an *occur
r
ence* of an Id marked
as Dead, so we must zap the OccInfo on cb before making the
binding x = cb. See Trac #5028.
...
...
compiler/simplCore/SimplCore.lhs
View file @
9005f91e
...
...
@@ -628,7 +628,7 @@ simplifyPgmIO pass@(CoreDoSimplify max_iterations mode)
, sz == sz -- Force it
= do {
-- Occurrence analysis
let { -- Note [Vectorisation declarations and occurences]
let { -- Note [Vectorisation declarations and occur
r
ences]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- During the 'InitialPhase' (i.e., before vectorisation), we need to make sure
-- that the right-hand sides of vectorisation declarations are taken into
...
...
compiler/stgSyn/CoreToStg.lhs
View file @
9005f91e
...
...
@@ -1076,7 +1076,7 @@ type FreeVarsInfo = VarEnv (Var, HowBound, StgBinderInfo)
--
-- All case/lambda-bound things are also mapped to
-- noBinderInfo, since we aren't interested in their
-- occurence info.
-- occur
r
ence info.
--
-- For ILX we track free var info for type variables too;
-- hence VarEnv not IdEnv
...
...
compiler/typecheck/TcMType.lhs
View file @
9005f91e
...
...
@@ -546,7 +546,7 @@ zonkQuantifiedTyVar :: TcTyVar -> TcM TcTyVar
-- default their kind (e.g. from OpenTypeKind to TypeKind)
-- -- see notes with Kind.defaultKind
-- The meta tyvar is updated to point to the new skolem TyVar. Now any
-- bound occurences of the original type variable will get zonked to
-- bound occur
r
ences of the original type variable will get zonked to
-- the immutable version.
--
-- We leave skolem TyVars alone; they are immutable.
...
...
docs/comm/exts/th.html
View file @
9005f91e
...
...
@@ -131,7 +131,7 @@ Core Language.Haskell.TH.Syntax.Type</pre>
appear.
</p>
<h3>
Binders Versus Occurences
</h3>
<h3>
Binders Versus Occur
r
ences
</h3>
<p>
Name lookups in the meta environment of the desugarer use two functions
with slightly different behaviour, namely
<code>
DsMeta.lookupOcc
</code>
...
...
docs/comm/the-beast/basicTypes.html
View file @
9005f91e
...
...
@@ -41,7 +41,7 @@
<code>
IdInfo
</code>
:
<p>
<dl>
<dt><a
name=
"occInfo"
>
Occurence information
</a>
<dt><a
name=
"occInfo"
>
Occur
r
ence information
</a>
<dd>
The
<code>
OccInfo
</code>
data type is defined in the module
<a
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/basicTypes/BasicTypes.lhs"
><code>
BasicTypes.lhs
</code></a>
.
Apart from the trivial
<code>
NoOccInfo
</code>
, it distinguishes
...
...
docs/comm/the-beast/renamer.html
View file @
9005f91e
...
...
@@ -194,7 +194,7 @@ data Provenance
<code>
RdrName
</code>
environment, which contains
<code>
Name
</code>
s for
all imported
<em>
and
</em>
all locally defined toplevel binders. Hence,
when the helpers of
<code>
rnSrcDecls
</code>
come across the
<em>
defining
</em>
occurences of a toplevel
<code>
RdrName
</code>
, they
<em>
defining
</em>
occur
r
ences of a toplevel
<code>
RdrName
</code>
, they
don't rename it by generating a new name, but they simply look up its
name in the global
<code>
RdrName
</code>
environment.
</p>
...
...
docs/comm/the-beast/simplifier.html
View file @
9005f91e
...
...
@@ -37,7 +37,7 @@
computes a set of
<em>
loop breakers
</em>
- a set of definitions that
together cut any possible loop in the binding group. It marks the
identifiers bound by these definitions as loop breakers by enriching
their
<a
href=
"basicTypes.html#occInfo"
>
occurence information.
</a>
Loop
their
<a
href=
"basicTypes.html#occInfo"
>
occur
r
ence information.
</a>
Loop
breakers will
<em>
never
</em>
be inlined by the simplifier; thus,
guaranteeing termination of the simplification procedure. (This is not
entirely accurate -- see
<a
href=
"#rules"
>
rewrite rules
</a>
below.)
...
...
docs/comm/the-beast/stg.html
View file @
9005f91e
...
...
@@ -75,10 +75,10 @@
<p>
The representation of STG language defined in
<a
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/stgSyn/StgSyn.lhs"
><code>
StgSyn
</code></a>
abstracts over both binders and occurences of variables. The type names
abstracts over both binders and occur
r
ences of variables. The type names
involved in this generic definition all carry the prefix
<code>
Gen
</code>
(such as in
<code>
GenStgBinding
</code>
). Instances of
these generic definitions, where both binders and occurences are of type
these generic definitions, where both binders and occur
r
ences are of type
<a
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/basicTypes/Id.lhs"
><code>
Id
</code></a><code>
.Id
</code>
are defined as type synonyms and use type names that drop the
...
...
docs/comm/the-beast/typecheck.html
View file @
9005f91e
...
...
@@ -21,7 +21,7 @@
GHC defines the abstract syntax of Haskell programs in
<a
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/hsSyn/HsSyn.lhs"
><code>
HsSyn
</code></a>
using a structure that abstracts over the concrete representation of
bound occurences of identifiers and patterns. The module
<a
bound occur
r
ences of identifiers and patterns. The module
<a
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/typecheck/TcHsSyn.lhs"
><code>
TcHsSyn
</code></a>
defines a number of helper function required by the type checker. Note
that the type
<a
...
...
@@ -248,7 +248,7 @@ tau -> tyvar
Expressions are type checked by
<a
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/typecheck/TcExpr.lhs"
><code>
TcExpr
</code>
.
</a>
<p>
Usage occurences of identifiers are processed by the function
Usage occur
r
ences of identifiers are processed by the function
<code>
tcId
</code>
whose main purpose is to
<a
href=
"#inst"
>
instantiate
overloaded identifiers.
</a>
It essentially calls
<code>
TcInst.instOverloadedFun
</code>
once for each universally
...
...
@@ -275,7 +275,7 @@ tau -> tyvar
href=
"http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ghc/compiler/typecheck/Inst.lhs"
><code>
Inst.lhs
</code>
.
</a>
<p>
The function
<code>
instOverloadedFun
</code>
is invoked for each
overloaded usage occurence of an identifier, where overloaded means that
overloaded usage occur
r
ence of an identifier, where overloaded means that
the type of the idendifier contains a non-trivial type constraint. It
proceeds in two steps: (1) Allocation of a method instance
(
<code>
newMethodWithGivenTy
</code>
) and (2) instantiation of functional
...
...
docs/ndp/haskell.sty
View file @
9005f91e
...
...
@@ -87,7 +87,7 @@
\ProvidesPackage
{
haskell
}
[2002/02/08 v1.1a Chilli's Haskell Style]
% NOTE: The sole purpose of the following is to work around what I believe is
% a bug in LaTeX. If the first occurence of \mathit in a document uses
% a bug in LaTeX. If the first occur
r
ence of \mathit in a document uses
% \bgroup and \egroup to enclose the argument (instead of { and }),
% \mathit does *not* apply to the argument. (I guess, some font
% initialisation stuff is getting in the way of parsing the argument.)
...
...
docs/ndp/vect.tex
View file @
9005f91e
...
...
@@ -243,7 +243,7 @@ Note that this is precisely the reason for the \<\parr{\cdot}\> instances for
\<\alpha\to\beta\>
and
\<
PA
\alpha\>
. A term of type
\<\forall\alpha
.
\sigma\>
will be lifted to a term of type
\<\parr
{
\forall\alpha
.PA
\alpha\to\vect
{
\sigma
}}
\>
which requires the
instances. Apart from closures, these are the only occurences of
\<
(
{
\to
}
)
\>
in
instances. Apart from closures, these are the only occur
r
ences of
\<
(
{
\to
}
)
\>
in
the transformed program, however.
...
...
docs/users_guide/glasgow_exts.xml
View file @
9005f91e
...
...
@@ -1103,7 +1103,7 @@ pattern (Show b) => ExNumPat b :: (Num a, Eq a) => T a
<listitem>
Matching:
<para>
A pattern synonym occur
a
nce in a pattern is evaluated by first
A pattern synonym occur
re
nce in a pattern is evaluated by first
matching against the pattern synonym itself, and then on the argument
patterns. For example, in the following program,
<literal>
f
</literal>
and
<literal>
f'
</literal>
are equivalent:
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a 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