summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorSimon Peyton Jones <simonpj@microsoft.com>2018-12-20 12:42:46 +0000
committerSimon Peyton Jones <simonpj@microsoft.com>2018-12-20 14:07:16 +0000
commita1c3ad0450baedadc223969dd2b09f59872a38e7 (patch)
treee71adc811629178451f275c418059b966766f7d7
parent557178619aa20d7c7789fe2c6225396429c77f70 (diff)
downloadhaskell-a1c3ad0450baedadc223969dd2b09f59872a38e7.tar.gz
Add solveLocalEqualities to tcHsPatSigType
This call plain missing, and as a result the casts messed up deep-skolemisation in tcSubType Fixes Trac #16033
-rw-r--r--compiler/typecheck/TcHsType.hs6
-rw-r--r--testsuite/tests/typecheck/should_compile/T16033.hs7
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T1
3 files changed, 13 insertions, 1 deletions
diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs
index 3b36281d4a..56a0ea0c34 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 0000000000..09be024af4
--- /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 a8e8cfe910..3fed2a9466 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, [''])