[commit: ghc] ghc-7.10: Fix #10031 by inverting a critical test in kick_out. (2387369)
git at git.haskell.org
git at git.haskell.org
Wed Jan 28 18:46:47 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-7.10
Link : http://ghc.haskell.org/trac/ghc/changeset/2387369c498f631bd3f4be2d6efe71773353acc5/ghc
>---------------------------------------------------------------
commit 2387369c498f631bd3f4be2d6efe71773353acc5
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Tue Jan 27 11:40:26 2015 -0500
Fix #10031 by inverting a critical test in kick_out.
Summary:
The documentation (Note [The flattening story] in TcFlatten) was
correct; it's just the implementation that was not.
Test in typecheck/should_compile/T10031
Test Plan: validate
Reviewers: austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D630
GHC Trac Issues: #10031
(cherry picked from commit cecf036fa10830a5e9861d1e6a2f8c22059fb4bb)
>---------------------------------------------------------------
2387369c498f631bd3f4be2d6efe71773353acc5
compiler/typecheck/TcInteract.hs | 2 +-
testsuite/tests/typecheck/should_compile/T10031.hs | 5 +++++
testsuite/tests/typecheck/should_compile/all.T | 1 +
3 files changed, 7 insertions(+), 1 deletion(-)
diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs
index c67e437..1d0d8e4 100644
--- a/compiler/typecheck/TcInteract.hs
+++ b/compiler/typecheck/TcInteract.hs
@@ -1033,7 +1033,7 @@ kick_out new_flavour new_eq_rel new_tv (IC { inert_eqs = tv_eqs
| can_rewrite ev
= case eq_rel of
NomEq -> not (rhs_ty `eqType` mkTyVarTy new_tv)
- ReprEq -> isTyVarExposed new_tv rhs_ty
+ ReprEq -> not (isTyVarExposed new_tv rhs_ty)
| otherwise
= True
diff --git a/testsuite/tests/typecheck/should_compile/T10031.hs b/testsuite/tests/typecheck/should_compile/T10031.hs
new file mode 100644
index 0000000..4ed45d3
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T10031.hs
@@ -0,0 +1,5 @@
+{-# LANGUAGE ScopedTypeVariables #-}
+module T10031 where
+import Data.Coerce
+coerce' :: Coercible b a => a -> b
+coerce' = coerce (\x -> x :: b) :: forall a b. Coercible b a => a -> b
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index df07a3e..cce92d0 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -439,3 +439,4 @@ test('T9834', normal, compile, [''])
test('T9892', normal, compile, [''])
test('T9971', normal, compile, [''])
test('T9999', normal, compile, [''])
+test('T10031', normal, compile, [''])
More information about the ghc-commits
mailing list