[Git][ghc/ghc][master] testsuite: Add testcase for #18129
Marge Bot
gitlab at gitlab.haskell.org
Wed May 13 06:08:35 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
9e4b981f by Ben Gamari at 2020-05-13T02:08:24-04:00
testsuite: Add testcase for #18129
- - - - -
2 changed files:
- + testsuite/tests/typecheck/should_compile/T18129.hs
- testsuite/tests/typecheck/should_compile/all.T
Changes:
=====================================
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)
+
=====================================
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, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e4b981ff7a0852c7bdc93039eed13582d923241
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e4b981ff7a0852c7bdc93039eed13582d923241
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200513/b6fbc6fd/attachment-0001.html>
More information about the ghc-commits
mailing list