summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2020-05-09 14:50:24 -0400
committerBen Gamari <ben@smart-cactus.org>2020-05-09 14:50:37 -0400
commit13f49ffb768865d57e052492f488e365e881eca8 (patch)
treed25d343df6fdef395a41fe52589c0a2e481b8763
parent86c77b36628dcce7bc9b066fc24c8c521fecc3ee (diff)
downloadhaskell-wip/T18129.tar.gz
testsuite: Add testcase for #18129wip/T18129
-rw-r--r--testsuite/tests/typecheck/should_compile/T18129.hs52
-rw-r--r--testsuite/tests/typecheck/should_compile/all.T1
2 files changed, 53 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T18129.hs b/testsuite/tests/typecheck/should_compile/T18129.hs
new file mode 100644
index 0000000000..933c381a9b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T18129.hs
@@ -0,0 +1,52 @@
+{-# LANGUAGE AllowAmbiguousTypes #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE UndecidableSuperClasses #-}
+
+module T18129 where
+
+import Data.Kind (Constraint)
+import Data.Proxy (Proxy)
+import Data.Typeable (Typeable)
+
+-- First, `generics-sop` code, intact.
+--
+type family
+ AllF (c :: k -> Constraint) (xs :: [k]) :: Constraint where
+ AllF _c '[] = ()
+ AllF c (x ': xs) = (c x, All c xs)
+
+class (AllF c xs, SListI xs) => All (c :: k -> Constraint) (xs :: [k])
+instance All c '[]
+instance (c x, All c xs) => All c (x ': xs) where
+
+class Top x
+instance Top x
+
+type SListI = All Top
+
+-- Next, user code, minimised.
+--
+data GADT
+ = forall (xs :: [*]) (a :: *)
+ . (Top a, All Typeable xs)
+ => GADT
+
+withSomePipe'
+ :: GADT
+ -> (forall (xs :: [*])
+ . (Proxy xs -> GADT)
+ -> GADT)
+ -> GADT
+withSomePipe' GADT f = f (const GADT)
+
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 03389993dd..56eecc0374 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -706,3 +706,4 @@ test('T18023', normal, compile, [''])
test('T18036', normal, compile, [''])
test('T18036a', normal, compile, [''])
test('T17873', normal, compile, [''])
+test('T18129', expect_broken(18129), compile, [''])