summaryrefslogtreecommitdiff
path: root/testsuite/tests/polykinds
diff options
context:
space:
mode:
authorSimon Peyton Jones <simon.peytonjones@gmail.com>2022-10-28 22:51:30 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-11-01 12:49:47 -0400
commit0560821f637fa2a4318fb068a969f4802acb5a89 (patch)
tree81f8e018b458c23f8c4003aaec3780665e617236 /testsuite/tests/polykinds
parent30e625e6d4bdd15960edce8ecc40b85ce3d72b28 (diff)
downloadhaskell-0560821f637fa2a4318fb068a969f4802acb5a89.tar.gz
Add accurate skolem info when quantifying
Ticket #22379 revealed that skolemiseQuantifiedTyVar was dropping the passed-in skol_info on the floor when it encountered a SkolemTv. Bad! Several TyCons thereby share a single SkolemInfo on their binders, which lead to bogus error reports.
Diffstat (limited to 'testsuite/tests/polykinds')
-rw-r--r--testsuite/tests/polykinds/T22379a.hs31
-rw-r--r--testsuite/tests/polykinds/T22379b.hs30
-rw-r--r--testsuite/tests/polykinds/all.T2
3 files changed, 63 insertions, 0 deletions
diff --git a/testsuite/tests/polykinds/T22379a.hs b/testsuite/tests/polykinds/T22379a.hs
new file mode 100644
index 0000000000..d4caa01048
--- /dev/null
+++ b/testsuite/tests/polykinds/T22379a.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE Haskell2010 #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+module Bug where
+
+import Data.Kind
+import Data.Proxy (Proxy)
+
+data Delayed (env :: Type) (c :: Type)
+data Handler (a :: Type)
+data Router (a :: Type)
+
+-- class decl, then type decl
+
+class HasServer api where
+ type ServerT api (m :: Type -> Type) :: Type
+
+ route ::
+ Proxy api
+ -> Delayed env (Server api)
+ -> Router env
+
+ hoistServerWithContext
+ :: Proxy api
+ -> (forall x. m x -> n x)
+ -> ServerT api m
+ -> ServerT api n
+
+type Server aqi = ServerT aqi Handler
+
diff --git a/testsuite/tests/polykinds/T22379b.hs b/testsuite/tests/polykinds/T22379b.hs
new file mode 100644
index 0000000000..78cd004090
--- /dev/null
+++ b/testsuite/tests/polykinds/T22379b.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE Haskell2010 #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+module Bug where
+
+import Data.Kind
+import Data.Proxy (Proxy)
+
+data Delayed (env :: Type) (c :: Type)
+data Handler (a :: Type)
+data Router (a :: Type)
+
+-- type decl, then class decl
+
+type Server aqi = ServerT aqi Handler
+
+class HasServer api where
+ type ServerT api (m :: Type -> Type) :: Type
+
+ route ::
+ Proxy api
+ -> Delayed env (Server api)
+ -> Router env
+
+ hoistServerWithContext
+ :: Proxy api
+ -> (forall x. m x -> n x)
+ -> ServerT api m
+ -> ServerT api n
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index fbe65d4b1c..721e41cebd 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -239,3 +239,5 @@ test('T19739a', normal, compile, [''])
test('T19739b', normal, compile, [''])
test('T19739c', normal, compile, [''])
test('T19739d', normal, compile, [''])
+test('T22379a', normal, compile, [''])
+test('T22379b', normal, compile, [''])