[commit: ghc] master: Add test cases for #7503, #14451 (aef5d82)
git at git.haskell.org
git at git.haskell.org
Mon Dec 3 16:34:55 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/aef5d82543bb642a65f63e1f05f245b9cddafd8c/ghc
>---------------------------------------------------------------
commit aef5d82543bb642a65f63e1f05f245b9cddafd8c
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Mon Dec 3 11:34:02 2018 -0500
Add test cases for #7503, #14451
At some point between 8.4 and 8.6, two things were fixed:
* The entirety of #14451.
* One of the test cases in #7503. I've added this as T7503a. The
other test case from that ticket still does /not/ work, so we'll
have to add T7503b some other day.
>---------------------------------------------------------------
aef5d82543bb642a65f63e1f05f245b9cddafd8c
testsuite/tests/typecheck/should_compile/T14451.hs | 28 ++++++++++++++++++++++
testsuite/tests/typecheck/should_compile/T7503a.hs | 18 ++++++++++++++
testsuite/tests/typecheck/should_compile/all.T | 2 ++
3 files changed, 48 insertions(+)
diff --git a/testsuite/tests/typecheck/should_compile/T14451.hs b/testsuite/tests/typecheck/should_compile/T14451.hs
new file mode 100644
index 0000000..a67ce74
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T14451.hs
@@ -0,0 +1,28 @@
+{-# Language KindSignatures, TypeOperators, PolyKinds, TypeOperators, ConstraintKinds, TypeFamilies, DataKinds, TypeInType, GADTs, AllowAmbiguousTypes, InstanceSigs, RankNTypes, UndecidableInstances #-}
+module T14451 where
+
+import Data.Kind
+
+data TyFun :: Type -> Type -> Type
+
+type a ~> b = TyFun a b -> Type
+
+type Cat ob = ob -> ob -> Type
+
+type family
+ Apply (f :: a ~> b) (x :: a) :: b where
+ Apply (CompSym2 f g) a = Comp f g a
+
+data CompSym2 :: (b ~> c) -> (a ~> b) -> (a ~> c)
+
+type a·b = Apply a b
+
+class Varpi (f :: i ~> j) where
+ type Dom (f :: i ~> j) :: Cat i
+ type Cod (f :: i ~> j) :: Cat j
+
+ varpa :: Dom f a a' -> Cod f (f·a) (f·a')
+
+type family
+ Comp (f::k1 ~> k) (g::k2 ~> k1) (a::k2) :: k where
+ Comp f g a = f · (g · a)
diff --git a/testsuite/tests/typecheck/should_compile/T7503a.hs b/testsuite/tests/typecheck/should_compile/T7503a.hs
new file mode 100644
index 0000000..61c0fb3
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T7503a.hs
@@ -0,0 +1,18 @@
+{-# LANGUAGE ExistentialQuantification, DataKinds, PolyKinds, KindSignatures, GADTs #-}
+module T7503a where
+ import Data.Kind
+ import GHC.Exts hiding (Any)
+
+ data WrappedType = forall a. WrapType a
+
+ data A :: WrappedType -> Type where
+ MkA :: forall (a :: Type). AW a -> A (WrapType a)
+
+ type AW (a :: k) = A (WrapType a)
+ type AW' (a :: k) = A (WrapType a)
+
+ class C (a :: k) where
+ aw :: AW a -- workaround: AW'
+
+ instance C [] where
+ aw = aw
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index be7ad3d..99c2259 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -401,6 +401,7 @@ test('type_in_type_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-v
test('T15370', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -funclutter-valid-hole-fits'])
test('T7408', normal, compile, [''])
test('UnboxStrictPrimitiveFields', normal, compile, [''])
+test('T7503a', normal, compile, [''])
test('T7541', normal, compile, [''])
test('T7562', normal, compile, [''])
test('T7641', normal, compile, [''])
@@ -596,6 +597,7 @@ test('T14396', [extra_files(['T14396.hs', 'T14396.hs-boot', 'T14396a.hs', 'T1439
test('T14434', [], run_command, ['$MAKE -s --no-print-directory T14434'])
test('MissingExportList01', normal, compile, [''])
test('MissingExportList02', normal, compile, [''])
+test('T14451', normal, compile, [''])
test('T14488', normal, compile, [''])
test('T14590', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits'])
# We omit the hpc/profasm ways because this test checks the
More information about the ghc-commits
mailing list