[commit: ghc] master: Add solveLocalEqualities to tcHsPatSigType (a1c3ad0)
git at git.haskell.org
git at git.haskell.org
Thu Dec 20 15:02:18 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a1c3ad0450baedadc223969dd2b09f59872a38e7/ghc
>---------------------------------------------------------------
commit a1c3ad0450baedadc223969dd2b09f59872a38e7
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Dec 20 12:42:46 2018 +0000
Add solveLocalEqualities to tcHsPatSigType
This call plain missing, and as a result the casts
messed up deep-skolemisation in tcSubType
Fixes Trac #16033
>---------------------------------------------------------------
a1c3ad0450baedadc223969dd2b09f59872a38e7
compiler/typecheck/TcHsType.hs | 6 +++++-
testsuite/tests/typecheck/should_compile/T16033.hs | 7 +++++++
testsuite/tests/typecheck/should_compile/all.T | 1 +
3 files changed, 13 insertions(+), 1 deletion(-)
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 3b36281..56a0ea0 100644
--- a/compiler/typecheck/TcHsType.hs
+++ b/compiler/typecheck/TcHsType.hs
@@ -2323,7 +2323,11 @@ tcHsPatSigType ctxt sig_ty
= addSigCtxt ctxt hs_ty $
do { sig_tkvs <- mapM new_implicit_tv sig_vars
; (wcs, sig_ty)
- <- tcWildCardBinders sig_wcs $ \ wcs ->
+ <- solveLocalEqualities "tcHsPatSigType" $
+ -- Always solve local equalities if possible,
+ -- else casts get in the way of deep skolemisation
+ -- (Trac #16033)
+ tcWildCardBinders sig_wcs $ \ wcs ->
tcExtendTyVarEnv sig_tkvs $
do { sig_ty <- tcHsOpenType hs_ty
; return (wcs, sig_ty) }
diff --git a/testsuite/tests/typecheck/should_compile/T16033.hs b/testsuite/tests/typecheck/should_compile/T16033.hs
new file mode 100644
index 0000000..09be024
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T16033.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+module T16033 where
+
+f :: (forall x. x -> forall y. y -> c) -> ()
+f (_ :: forall a. a -> forall b. b -> c) = ()
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index a8e8cfe..3fed2a9 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -657,3 +657,4 @@ test('T15645', normal, compile, ['-Wwarn=missing-monadfail-instances'])
test('T15778', normal, compile, [''])
test('T14761c', normal, compile, [''])
test('T16008', normal, compile, [''])
+test('T16033', normal, compile, [''])
More information about the ghc-commits
mailing list