diff --git a/testsuite/tests/polykinds/T6020a.hs b/testsuite/tests/polykinds/T6020a.hs new file mode 100644 index 0000000000000000000000000000000000000000..00689786c345dfe0ca199df4dc11d35238b6b226 --- /dev/null +++ b/testsuite/tests/polykinds/T6020a.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE DataKinds, FunctionalDependencies, FlexibleInstances, + UndecidableInstances, PolyKinds, KindSignatures, + ConstraintKinds, FlexibleContexts, GADTs #-} + +module T6020a where + +class Id (a :: k) (b :: k) | b -> a +instance a ~ b => Id a b + +class Test (x :: a) (y :: a) +instance (Id x y, Id y z) => Test x z + +test :: Test True True => () +test = () + + diff --git a/testsuite/tests/polykinds/T6044.hs b/testsuite/tests/polykinds/T6044.hs new file mode 100644 index 0000000000000000000000000000000000000000..dd35be90176bc25696fc4206c251b4ec61d31bb8 --- /dev/null +++ b/testsuite/tests/polykinds/T6044.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PolyKinds, DataKinds, TypeFamilies, KindSignatures #-} + +module T6044 where + +type family Foo (a :: k) :: Maybe k +type instance Foo a = Just a diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 92f6414ac4cafb520ed5d087a110fc5443e6de78..5f136b16b9b21541615e678864c7ceaec9e77cdb 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -41,3 +41,5 @@ test('T6025', normal, run_command, ['$MAKE -s --no-print-directory T6025']) test('T6002', normal, compile, ['']) test('T6039', normal, compile_fail, ['']) test('T6021', normal, compile_fail, ['']) +test('T6020a', normal, compile, ['']) +test('T6044', normal, compile, [''])