diff options
author | Ryan Scott <ryan.gl.scott@gmail.com> | 2018-12-03 11:34:02 -0500 |
---|---|---|
committer | Ryan Scott <ryan.gl.scott@gmail.com> | 2018-12-03 11:34:02 -0500 |
commit | aef5d82543bb642a65f63e1f05f245b9cddafd8c (patch) | |
tree | 0a3ba58ffbab5840d53d6dac43717deceeff9aba | |
parent | a46511a88e719d990285f06b29a38839b3e0a0bf (diff) | |
download | haskell-aef5d82543bb642a65f63e1f05f245b9cddafd8c.tar.gz |
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.
-rw-r--r-- | testsuite/tests/typecheck/should_compile/T14451.hs | 28 | ||||
-rw-r--r-- | testsuite/tests/typecheck/should_compile/T7503a.hs | 18 | ||||
-rw-r--r-- | testsuite/tests/typecheck/should_compile/all.T | 2 |
3 files changed, 48 insertions, 0 deletions
diff --git a/testsuite/tests/typecheck/should_compile/T14451.hs b/testsuite/tests/typecheck/should_compile/T14451.hs new file mode 100644 index 0000000000..a67ce74537 --- /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 0000000000..61c0fb34e2 --- /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 be7ad3d8c6..99c2259639 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 |