Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
Alex D
GHC
Commits
c6b04865
Commit
c6b04865
authored
Jan 11, 2017
by
Gabor Greif
💬
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Typos in manual, comments and tests
parent
f9df77e4
Changes
17
Show whitespace changes
Inline
Side-by-side
Showing
17 changed files
with
25 additions
and
25 deletions
+25
-25
compiler/coreSyn/CorePrep.hs
compiler/coreSyn/CorePrep.hs
+1
-1
compiler/coreSyn/CoreSyn.hs
compiler/coreSyn/CoreSyn.hs
+1
-1
compiler/coreSyn/CoreUtils.hs
compiler/coreSyn/CoreUtils.hs
+1
-1
compiler/iface/TcIface.hs
compiler/iface/TcIface.hs
+1
-1
compiler/llvmGen/Llvm/PpLlvm.hs
compiler/llvmGen/Llvm/PpLlvm.hs
+1
-1
compiler/rename/RnTypes.hs
compiler/rename/RnTypes.hs
+4
-4
compiler/simplCore/SimplUtils.hs
compiler/simplCore/SimplUtils.hs
+1
-1
compiler/typecheck/TcRnExports.hs
compiler/typecheck/TcRnExports.hs
+2
-2
compiler/typecheck/TcType.hs
compiler/typecheck/TcType.hs
+3
-3
docs/users_guide/separate_compilation.rst
docs/users_guide/separate_compilation.rst
+3
-3
libraries/base/Data/List/NonEmpty.hs
libraries/base/Data/List/NonEmpty.hs
+1
-1
testsuite/tests/perf/compiler/all.T
testsuite/tests/perf/compiler/all.T
+1
-1
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered08_A.hs
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered08_A.hs
+1
-1
testsuite/tests/typecheck/should_compile/tc186.hs
testsuite/tests/typecheck/should_compile/tc186.hs
+1
-1
testsuite/tests/typecheck/should_compile/tc201.hs
testsuite/tests/typecheck/should_compile/tc201.hs
+1
-1
testsuite/tests/typecheck/should_fail/T10715.hs
testsuite/tests/typecheck/should_fail/T10715.hs
+1
-1
testsuite/tests/typecheck/should_fail/tcfail135.hs
testsuite/tests/typecheck/should_fail/tcfail135.hs
+1
-1
No files found.
compiler/coreSyn/CorePrep.hs
View file @
c6b04865
...
...
@@ -1316,7 +1316,7 @@ allLazyNested is_rec (Floats IfUnboxedOk _) = isNonRec is_rec
-- x = lazy @ (forall a. a) y @ Bool
--
-- When we inline 'x' after eliminating 'lazy', we need to replace
-- occurences of 'x' with 'y @ bool', not just 'y'. Situations like
-- occur
r
ences of 'x' with 'y @ bool', not just 'y'. Situations like
-- this can easily arise with higher-rank types; thus, cpe_env must
-- map to CoreExprs, not Ids.
...
...
compiler/coreSyn/CoreSyn.hs
View file @
c6b04865
...
...
@@ -557,7 +557,7 @@ data Tickish id =
-- valid. Note that it is still undesirable though, as this reduces
-- their usefulness for debugging and profiling. Therefore we will
-- generally try only to make use of this property where it is
-- nec
c
essary to enable optimizations.
-- necessary to enable optimizations.
|
SourceNote
{
sourceSpan
::
RealSrcSpan
-- ^ Source covered
,
sourceName
::
String
-- ^ Name for source location
...
...
compiler/coreSyn/CoreUtils.hs
View file @
c6b04865
...
...
@@ -591,7 +591,7 @@ filterAlts _tycon inst_tys imposs_cons alts
impossible_alt
_
_
=
False
refineDefaultAlt
::
[
Unique
]
->
TyCon
->
[
Type
]
->
[
AltCon
]
-- Constructors tha cannot match the DEFAULT (if any)
->
[
AltCon
]
-- Constructors tha
t
cannot match the DEFAULT (if any)
->
[
CoreAlt
]
->
(
Bool
,
[
CoreAlt
])
-- Refine the default alterantive to a DataAlt,
...
...
compiler/iface/TcIface.hs
View file @
c6b04865
...
...
@@ -271,7 +271,7 @@ mergeIfaceDecls = plusOccEnv_C mergeIfaceDecl
-- (a) need a stronger acyclicity check which considers *all*
-- possible choices from a merge, or (b) we must find a selection
-- of declarations which is acyclic, and show that this is always
-- the "best" choice we could have made (ezyang conjecture
'
s this
-- the "best" choice we could have made (ezyang conjectures this
-- is the case but does not have a proof). For now this is
-- not implemented.
--
...
...
compiler/llvmGen/Llvm/PpLlvm.hs
View file @
c6b04865
...
...
@@ -137,7 +137,7 @@ ppLlvmFunction fun =
$+$
newLine
$+$
newLine
-- | Print out a function def
e
nition header.
-- | Print out a function def
i
nition header.
ppLlvmFunctionHeader
::
LlvmFunctionDecl
->
[
LMString
]
->
SDoc
ppLlvmFunctionHeader
(
LlvmFunctionDecl
n
l
c
r
varg
p
a
)
args
=
let
varg'
=
case
varg
of
...
...
compiler/rename/RnTypes.hs
View file @
c6b04865
...
...
@@ -1530,7 +1530,7 @@ extractHsTyRdrTyVars :: LHsType RdrName -> RnM FreeKiTyVars
-- It's used when making the for-alls explicit.
-- Does not return any wildcards
-- When the same name occurs multiple times in the types, only the first
-- occurence is returned.
-- occur
r
ence is returned.
-- See Note [Kind and type-variable binders]
extractHsTyRdrTyVars
ty
=
do
{
FKTV
kis
k_set
tys
t_set
all
<-
extract_lty
TypeLevel
ty
emptyFKTV
...
...
@@ -1540,20 +1540,20 @@ extractHsTyRdrTyVars ty
-- | Extracts free type and kind variables from types in a list.
-- When the same name occurs multiple times in the types, only the first
-- occurence is returned and the rest is filtered out.
-- occur
r
ence is returned and the rest is filtered out.
-- See Note [Kind and type-variable binders]
extractHsTysRdrTyVars
::
[
LHsType
RdrName
]
->
RnM
FreeKiTyVars
extractHsTysRdrTyVars
tys
=
rmDupsInRdrTyVars
<$>
extractHsTysRdrTyVarsDups
tys
-- | Extracts free type and kind variables from types in a list.
-- When the same name occurs multiple times in the types, all occurences
-- When the same name occurs multiple times in the types, all occur
r
ences
-- are returned.
extractHsTysRdrTyVarsDups
::
[
LHsType
RdrName
]
->
RnM
FreeKiTyVars
extractHsTysRdrTyVarsDups
tys
=
extract_ltys
TypeLevel
tys
emptyFKTV
-- | Removes multiple occurences of the same name from FreeKiTyVars.
-- | Removes multiple occur
r
ences of the same name from FreeKiTyVars.
rmDupsInRdrTyVars
::
FreeKiTyVars
->
FreeKiTyVars
rmDupsInRdrTyVars
(
FKTV
kis
k_set
tys
t_set
all
)
=
FKTV
(
nubL
kis
)
k_set
(
nubL
tys
)
t_set
(
nubL
all
)
...
...
compiler/simplCore/SimplUtils.hs
View file @
c6b04865
...
...
@@ -1121,7 +1121,7 @@ only have *forward* references. Hence, it's safe to discard the binding
NOTE: This isn't our last opportunity to inline. We're at the binding
site right now, and we'll get another opportunity when we get to the
ocurrence(s)
oc
c
urrence(s)
Note that we do this unconditional inlining only for trival RHSs.
Don't inline even WHNFs inside lambdas; doing so may simply increase
...
...
compiler/typecheck/TcRnExports.hs
View file @
c6b04865
...
...
@@ -403,7 +403,7 @@ instance Outputable ChildLookupResult where
ppr
(
FoundFL
fls
)
=
text
"FoundFL:"
<+>
ppr
fls
ppr
(
NameErr
_
)
=
text
"Error"
-- Left biased accumulation monoid. Chooses the left-most positive occurence.
-- Left biased accumulation monoid. Chooses the left-most positive occur
r
ence.
instance
Monoid
ChildLookupResult
where
mempty
=
NameNotFound
NameNotFound
`
mappend
`
m2
=
m2
...
...
@@ -568,7 +568,7 @@ data DisambigInfo
instance
Monoid
DisambigInfo
where
mempty
=
NoOccurence
-- This is the key line: We prefer disambiguated occurences to other
-- This is the key line: We prefer disambiguated occur
r
ences to other
-- names.
UniqueOccurence
_
`
mappend
`
DisambiguatedOccurence
g'
=
DisambiguatedOccurence
g'
DisambiguatedOccurence
g'
`
mappend
`
UniqueOccurence
_
=
DisambiguatedOccurence
g'
...
...
compiler/typecheck/TcType.hs
View file @
c6b04865
...
...
@@ -280,7 +280,7 @@ reasons:
TyVars, bring 'k' and 'a' into scope, and kind check the
signature for 'foo'. In doing so we call solveEqualities to
solve any kind equalities in foo's signature. So the solver
may see free occurences of 'k'.
may see free occur
r
ences of 'k'.
It's convenient to simply treat these TyVars as skolem constants,
which of course they are. So
...
...
@@ -930,7 +930,7 @@ data TcDepVars -- See Note [Dependent type variables]
=
DV
{
dv_kvs
::
DTyCoVarSet
-- "kind" variables (dependent)
,
dv_tvs
::
DTyVarSet
-- "type" variables (non-dependent)
-- A variable may appear in both sets
-- E.g. T k (x::k) The first occurence of k makes it
-- E.g. T k (x::k) The first occur
r
ence of k makes it
-- show up in dv_tvs, the second in dv_kvs
-- See Note [Dependent type variables]
}
...
...
@@ -982,7 +982,7 @@ So: dv_kvs are the kind variables of the type
Note that
* A variable can occur in both.
T k (x::k) The first occurence of k makes it
T k (x::k) The first occur
r
ence of k makes it
show up in dv_tvs, the second in dv_kvs
* We include any coercion variables in the "dependent",
...
...
docs/users_guide/separate_compilation.rst
View file @
c6b04865
...
...
@@ -845,13 +845,13 @@ to ``hs-boot`` files, but with some slight changes:
type family ClosedFam a where ..
The ``..`` is meant literally -- you shou
d
l write two dots in
The ``..`` is meant literally -- you shoul
d
write two dots in
your file. The ``where`` clause distinguishes closed families
from open ones.
- A data type declaration can either be given in full, exactly
as in Haskell, or it can be given abstractly, by omitting the '='
sign and everything tha follows. For example: ::
sign and everything tha
t
follows. For example: ::
signature A where
data T a b
...
...
@@ -907,7 +907,7 @@ to ``hs-boot`` files, but with some slight changes:
These declarations can be implemented by type synonyms
of kind ``Constraint``; this can be useful if you want to parametrize
over a constraint in functions. For example, with the
``ConstraintKinds`` extension, this type synonym is avalid
``ConstraintKinds`` extension, this type synonym is a
valid
implementation of the signature above::
module A where
...
...
libraries/base/Data/List/NonEmpty.hs
View file @
c6b04865
...
...
@@ -491,7 +491,7 @@ unzip :: Functor f => f (a,b) -> (f a, f b)
unzip
xs
=
(
fst
<$>
xs
,
snd
<$>
xs
)
-- | The 'nub' function removes duplicate elements from a list. In
-- particular, it keeps only the first occurence of each element.
-- particular, it keeps only the first occur
r
ence of each element.
-- (The name 'nub' means \'essence\'.)
-- It is a special case of 'nubBy', which allows the programmer to
-- supply their own inequality test.
...
...
testsuite/tests/perf/compiler/all.T
View file @
c6b04865
...
...
@@ -427,7 +427,7 @@ test('T5631',
# 2015-12-21: 1198327544 (Mac) TypeApplications (will fix with #11196)
# 2015-03-18: 1124068664 (Mac) optimize Unify & zonking
# 2016-10-19: 1024926024 (amd64/Linux) Refactor traceRn interface (#12617)
# 2016-11-10: 1077429456 (amd64/Linux) Stop -dno-debug-output supressing -ddump-tc-trace
# 2016-11-10: 1077429456 (amd64/Linux) Stop -dno-debug-output sup
p
ressing -ddump-tc-trace
only_ways
(['
normal
'])
],
...
...
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered08_A.hs
View file @
c6b04865
{-# LANGUAGE OverlappingInstances #-}
{-# OPTIONS_GHC -w #-}
-- Turn off deprecation for OverlappingInstances
-- | Safe, as we now check at overlap occurence, not def
e
nition.
-- | Safe, as we now check at overlap occur
r
ence, not def
i
nition.
module
UnsafeInfered08_A
where
g
::
Int
...
...
testsuite/tests/typecheck/should_compile/tc186.hs
View file @
c6b04865
...
...
@@ -4,7 +4,7 @@
-- and the constraint (Foo (t::? -> s::*)) didn't match Foo (a::* -> b::*).
-- Solution is to zap the expected type in TcEpxr.tc_expr(HsOverLit).
module
Shou
d
lCompile
where
module
Shoul
d
Compile
where
class
Foo
a
where
foo
::
a
...
...
testsuite/tests/typecheck/should_compile/tc201.hs
View file @
c6b04865
...
...
@@ -14,7 +14,7 @@ soon).
-}
module
Shou
d
lCompile
where
module
Shoul
d
Compile
where
class
(
Monad
m
)
=>
Stream
m
h
|
h
->
m
where
vMkIOError
::
h
->
Int
...
...
testsuite/tests/typecheck/should_fail/T10715.hs
View file @
c6b04865
...
...
@@ -7,7 +7,7 @@ import Data.Ord ( Down ) -- convenient newtype
data
X
a
-- See Trac #10715 for a long discussion about whether
-- this shou
d
l be accepted or not.
-- this shoul
d
be accepted or not.
--
-- But in Trac #12466 we decided to accept contradictory
-- type signatures, so definition is now accepeted even
...
...
testsuite/tests/typecheck/should_fail/tcfail135.hs
View file @
c6b04865
-- A missing kind check made GHC 6.4 crash on this one
module
Shou
d
lFail
where
module
Shoul
d
Fail
where
class
Foo
f
where
baa
::
f
a
->
f
...
...
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