Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
4,247
Issues
4,247
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
398
Merge Requests
398
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
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
Glasgow Haskell Compiler
GHC
Commits
a3f7517e
Commit
a3f7517e
authored
Apr 30, 2015
by
Gabor Greif
💬
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Typo fixes (mostly in comments)
parent
b83160d0
Changes
10
Hide whitespace changes
Inline
Side-by-side
Showing
10 changed files
with
27 additions
and
27 deletions
+27
-27
compiler/rename/RnExpr.hs
compiler/rename/RnExpr.hs
+1
-1
compiler/rename/RnSource.hs
compiler/rename/RnSource.hs
+1
-1
compiler/rename/RnTypes.hs
compiler/rename/RnTypes.hs
+1
-1
compiler/typecheck/TcInteract.hs
compiler/typecheck/TcInteract.hs
+14
-14
compiler/typecheck/TcRnTypes.hs
compiler/typecheck/TcRnTypes.hs
+1
-1
compiler/typecheck/TcSMonad.hs
compiler/typecheck/TcSMonad.hs
+1
-1
docs/users_guide/glasgow_exts.xml
docs/users_guide/glasgow_exts.xml
+2
-2
testsuite/tests/indexed-types/should_compile/T10226.hs
testsuite/tests/indexed-types/should_compile/T10226.hs
+2
-2
testsuite/tests/programs/andy_cherry/DataTypes.hs
testsuite/tests/programs/andy_cherry/DataTypes.hs
+3
-3
testsuite/tests/typecheck/should_compile/T10009.hs
testsuite/tests/typecheck/should_compile/T10009.hs
+1
-1
No files found.
compiler/rename/RnExpr.hs
View file @
a3f7517e
...
...
@@ -748,7 +748,7 @@ rnStmt ctxt _ (L loc (TransStmt { trS_stmts = stmts, trS_by = by, trS_form = for
;
(
thing
,
fvs_thing
)
<-
thing_inside
bndrs
;
let
fvs
=
fvs_by
`
plusFV
`
fvs_thing
used_bndrs
=
filter
(`
elemNameSet
`
fvs
)
bndrs
-- The paper (Fig 5) has a bug here; we must treat any free var
ai
ble
-- The paper (Fig 5) has a bug here; we must treat any free var
ia
ble
-- of the "thing inside", **or of the by-expression**, as used
;
return
((
by'
,
used_bndrs
,
thing
),
fvs
)
}
...
...
compiler/rename/RnSource.hs
View file @
a3f7517e
...
...
@@ -100,7 +100,7 @@ rnSrcDecls extra_deps group@(HsGroup { hs_valds = val_decls,
-- because they do not have value declarations.
-- Aso step (C) depends on datacons and record fields
--
-- * Pattern synonyms, bec
ua
se they (and data constructors)
-- * Pattern synonyms, bec
au
se they (and data constructors)
-- are needed for rnTopBindLHS (Trac #9889)
--
-- * For hs-boot files, include the value signatures
...
...
compiler/rename/RnTypes.hs
View file @
a3f7517e
...
...
@@ -871,7 +871,7 @@ opTyErr _ ty = pprPanic "opTyErr: Not an op" (ppr ty)
Note [Kind and type-variable binders]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
In a type signature we may implicitly bind type var
ai
ble and, more
In a type signature we may implicitly bind type var
ia
ble and, more
recently, kind variables. For example:
* f :: a -> a
f = ...
...
...
compiler/typecheck/TcInteract.hs
View file @
a3f7517e
...
...
@@ -184,7 +184,7 @@ solveSimpleWanteds simples
solve_simple_wanteds
::
WantedConstraints
->
TcS
(
Bool
,
WantedConstraints
)
-- Try solving these constraints
-- Return True iff some unification happ
p
ened *during unflattening*
-- Return True iff some unification happened *during unflattening*
-- because this is a form of improvement
-- See Note [The improvement story]
-- Affects the unification state (of course) but not the inert set
...
...
@@ -203,7 +203,7 @@ solve_simple_wanteds (WC { wc_simple = simples1, wc_insol = insols1, wc_impl = i
try_improvement
::
WantedConstraints
->
TcS
(
Bool
,
WantedConstraints
)
-- See Note [The improvement story]
-- Try doing improvement on these simple constraints
-- Return True iff some unification happ
p
ened
-- Return True iff some unification happened
-- Affects the unification state (of course) but not the inert set
try_improvement
wc
@
(
WC
{
wc_simple
=
simples
,
wc_insol
=
insols
,
wc_impl
=
implics
})
|
isEmptyBag
simples
...
...
@@ -243,7 +243,7 @@ try_improvement wc@(WC { wc_simple = simples, wc_insol = insols, wc_impl = impli
usefulToFloat
::
(
TcPredType
->
Bool
)
->
Ct
->
Bool
usefulToFloat
is_useful_pred
ct
-- The constraint is un-flattened and de-can
n
onicalised
usefulToFloat
is_useful_pred
ct
-- The constraint is un-flattened and de-canonicalised
=
is_meta_var_eq
pred
&&
is_useful_pred
pred
where
pred
=
ctPred
ct
...
...
@@ -268,7 +268,7 @@ usefulToFloat is_useful_pred ct -- The constraint is un-flattened and de-canno
{- Note [The improvement story]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The goal of "improvement" is to use functional depen
e
dencies,
The goal of "improvement" is to use functional dependencies,
type-function injectivity, etc, to derive some extra equalities that
could let us unify one or more meta-variables, and hence make progress.
...
...
@@ -309,7 +309,7 @@ Some notes about this
Note [Orient equalities with flatten-meta-vars on the left]
Unify mm := State fmv:
[W] MonadState ss (State fmv), [W] Any ~ fmv, [W] fmv ~ ss
Alas the ins
at
nce does not match!! So now we are stuck.
Alas the ins
ta
nce does not match!! So now we are stuck.
Unflatten: with fmv := Any, and ss := Any
[W] MonadState Any (State Any)
...
...
@@ -383,7 +383,7 @@ Some notes about this
[W] w5: fsk1 ~ fmv1 -- From F a ~ F beta
-- using flat-cache
Solving (step 1) makes no
t
progress. So unflatten again
Solving (step 1) makes no progress. So unflatten again
[W] w3: UnF (F beta) ~ beta
[W] w5: fsk1 ~ F beta
...
...
@@ -394,7 +394,7 @@ Some notes about this
[D] fmv1 ~ fsk1 -- (B) From F a ~ F beta
-- NB: put fmv on left
--> rewrite (A) with (B), and m
e
tch with g2
--> rewrite (A) with (B), and m
a
tch with g2
[D] F beta ~ fmv1
[D] fmv2 ~ fsk2 -- (C)
[D] fmv2 ~ beta -- (D)
...
...
@@ -406,7 +406,7 @@ Some notes about this
[D] beta ~ fsk2 -- (E)
[D] fmv1 ~ fsk1
-- Now we can unify beta! Halelujah!
-- Now we can unify beta! Hal
l
elujah!
Note [Insolubles and improvement]
...
...
@@ -427,7 +427,7 @@ Note [Do not float kind-incompatible equalities]
If we have (t::* ~ s::*->*), we'll get a Derived insoluble equality.
If we float the equality outwards, we'll get *another* Derived
insoluble equality one level out, so the same error will be reported
twice. So we refrain from floating such equalities
twice. So we refrain from floating such equalities
.
-}
-- The main solver loop implements Note [Basic Simplifier Plan]
...
...
@@ -1649,7 +1649,7 @@ doTopReactFunEq work_item@(CFunEqCan { cc_ev = old_ev, cc_fun = fam_tc
-- final_co :: fsk ~ rhs_ty
;
new_ev
<-
newGivenEvVar
deeper_loc
(
mkTcEqPred
(
mkTyVarTy
fsk
)
rhs_ty
,
EvCoercion
final_co
)
;
emitWorkNC
[
new_ev
]
-- Non-can
n
onical; that will mean we flatten rhs_ty
;
emitWorkNC
[
new_ev
]
-- Non-canonical; that will mean we flatten rhs_ty
;
stopWith
old_ev
"Fun/Top (given)"
}
|
not
(
fsk
`
elemVarSet
`
tyVarsOfType
rhs_ty
)
...
...
@@ -1885,7 +1885,7 @@ It's exactly the same with implicit parameters, except that the
Note [When improvement happens during solving]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Improvement for functional dependencies or type-function injectivity
means emitting a Derived equality constraint by iteracting the work
means emitting a Derived equality constraint by i
n
teracting the work
item with an inert item, or with the top-level instances. e.g.
class C a b | a -> b
...
...
@@ -1897,9 +1897,9 @@ but not Wanted. Reason:
* Given: we want to spot Given/Given inconsistencies because that means
unreachable code. See typecheck/should_fail/FDsFromGivens
* Derived: during the improvment phase (i.e. when handling Derived
* Derived: during the improv
e
ment phase (i.e. when handling Derived
constraints) we also do improvement for functional dependencies. e.g.
And similarly wrt top-level instances.
And similarly wrt top-level instances.
* Wanted: spotting fundep improvements is somewhat inefficient, and
and if we can solve without improvement so much the better.
...
...
@@ -1937,7 +1937,7 @@ Consider class Het a b | a -> b where
The two instances don't actually conflict on their fundeps,
although it's pretty strange. So they are both accepted. Now
try [W] GHet (K Int) (K Bool)
This triggers fudeps from both instance decls;
This triggers fu
n
deps from both instance decls;
[D] K Bool ~ K [a]
[D] K Bool ~ K beta
And there's a risk of complaining about Bool ~ [a]. But in fact
...
...
compiler/typecheck/TcRnTypes.hs
View file @
a3f7517e
...
...
@@ -1312,7 +1312,7 @@ see dropDerivedWC. For example
an unsolved [D] (Eq a) as well.
* If we have [W] a ~ Int, [W] a ~ Bool, improvement will generate
[D] Int ~ Bool, and we don't want to report that bec
ua
se it's incomprehensible.
[D] Int ~ Bool, and we don't want to report that bec
au
se it's incomprehensible.
That is why we don't rewrite wanteds with wanteds!
But (tiresomely) we do keep *some* Derived insolubles:
...
...
compiler/typecheck/TcSMonad.hs
View file @
a3f7517e
...
...
@@ -1470,7 +1470,7 @@ unifyTyVar :: TcTyVar -> TcType -> TcS ()
-- We keep track of whether we have done any unifications in tcs_unified,
-- but only for *non-flatten* meta-vars
--
-- We should never unify the same var
a
iable twice!
-- We should never unify the same variable twice!
unifyTyVar
tv
ty
=
ASSERT2
(
isMetaTyVar
tv
,
ppr
tv
)
TcS
$
\
env
->
...
...
docs/users_guide/glasgow_exts.xml
View file @
a3f7517e
...
...
@@ -1175,7 +1175,7 @@ so function <literal>f</literal> is rejected because the type signature is <lite
(To see this, imagine expanding the pattern synonym.)
</para>
<para>
On the other hand, function
<literal>
g
</literal>
works fine, bec
ua
se matching against
<literal>
P2
</literal>
On the other hand, function
<literal>
g
</literal>
works fine, bec
au
se matching against
<literal>
P2
</literal>
(which wraps the GADT
<literal>
S
</literal>
) provides the local equality
<literal>
(a~Bool)
</literal>
.
If you were to give an explicit pattern signature
<literal>
P2 :: Bool -> S Bool
</literal>
, then
<literal>
P2
</literal>
would become less polymorphic, and would behave exactly like
<literal>
P1
</literal>
so that
<literal>
g
</literal>
...
...
@@ -8808,7 +8808,7 @@ Notice the two different types reported for the two different occurrences of <li
<listitem><para>
No language extension is required to use typed holes. The lexeme "
<literal>
_
</literal>
" was previously
illegal in Haskell, but now has a more informative error message. The lexeme "
<literal>
_x
</literal>
"
is a perfectly legal var
ai
ble, and its behaviour is unchanged when it is in scope. For example
is a perfectly legal var
ia
ble, and its behaviour is unchanged when it is in scope. For example
<programlisting>
f _x = _x + 1
</programlisting>
...
...
testsuite/tests/indexed-types/should_compile/T10226.hs
View file @
a3f7517e
...
...
@@ -18,7 +18,7 @@ showFromF fa = undefined
--
-- > b ~ F a /\ Show a /\ FInv (F a) ~ a
--
-- Introducing an interme
id
ate variable `x` for the result of `F a` gives us
-- Introducing an interme
di
ate variable `x` for the result of `F a` gives us
--
-- > b ~ F a /\ Show a /\ FInv x ~ a /\ F a ~ x
--
...
...
@@ -44,7 +44,7 @@ showFromF' = showFromF
{-------------------------------------------------------------------------------
In 7.10 the definition of showFromF' is not accepted, but it gets stranger.
In 7.10 we cannot _call_ showFromF at all
all
, even at a concrete type. Below
In 7.10 we cannot _call_ showFromF at all, even at a concrete type. Below
we try to call it at type b ~ Int. It would need to show
> Show (FInv Int) /\ F (FInt Int) ~ Int
...
...
testsuite/tests/programs/andy_cherry/DataTypes.hs
View file @
a3f7517e
...
...
@@ -218,9 +218,9 @@
xs
|
all
isDigit
xs
&&
not
(
null
xs
)
->
Just
(
read
xs
)
_
->
Nothing
result
=
mkResult
(
getTagStr
"Result"
"*"
tags
)
white
=
can
n
on
(
getTagStr
"White"
"?"
tags
)
white
=
canon
(
getTagStr
"White"
"?"
tags
)
whiteElo
=
getTagStr
"WhiteElo"
""
tags
black
=
can
n
on
(
getTagStr
"Black"
"?"
tags
)
black
=
canon
(
getTagStr
"Black"
"?"
tags
)
blackElo
=
getTagStr
"BlackElo"
""
tags
opening
=
getOpening
(
getTagStr
"ECO"
""
tags
)
...
...
@@ -240,7 +240,7 @@
getMonth
"11"
=
"Nov"
getMonth
"12"
=
"Dec"
can
n
on
name
=
case
span
(
/=
','
)
name
of
canon
name
=
case
span
(
/=
','
)
name
of
(
a
,[
','
,
' '
,
b
])
->
b
:
". "
++
a
(
a
,[
','
,
b
])
->
b
:
". "
++
a
(
a
,
','
:
' '
:
b
)
->
b
++
" "
++
a
...
...
testsuite/tests/typecheck/should_compile/T10009.hs
View file @
a3f7517e
...
...
@@ -44,7 +44,7 @@ g _ = f (undefined :: F a)
[D] fmv1 ~ fsk1 -- (B) From F a ~ F beta
-- NB: put fmv on left
--> rewrite (A) with (B), and m
e
tch with g2
--> rewrite (A) with (B), and m
a
tch with g2
[D] F beta ~ fmv1
[D] fmv2 ~ fsk2 -- (C)
...
...
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