diff --git a/testsuite/tests/deriving/should_fail/Roles12.stderr b/testsuite/tests/deriving/should_fail/Roles12.stderr index e7f9329f6a4b887fc31dda8136d9dbe6f9f3d910..ad8c25eecbe19d3f6ed41866ba1e058346f1a3bf 100644 --- a/testsuite/tests/deriving/should_fail/Roles12.stderr +++ b/testsuite/tests/deriving/should_fail/Roles12.stderr @@ -1,6 +1,7 @@ Roles12.hs:5:6: - Type constructor ‛T’ has conflicting definitions in the module and its hs-boot file + Type constructor ‛T’ has conflicting definitions in the module + and its hs-boot file Main module: data T a@P No C type associated RecFlag Recursive, Promotable diff --git a/testsuite/tests/indexed-types/should_compile/ClosedFam1.hs b/testsuite/tests/indexed-types/should_compile/ClosedFam1.hs new file mode 100644 index 0000000000000000000000000000000000000000..40c56db1bf24c3eaa07279fbff73a058cfddc3b3 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/ClosedFam1.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies #-} + +module ClosedFam1 where + +import {-# SOURCE #-} ClosedFam1 + +type family Foo a where + Foo Int = Bool + Foo [a] = Maybe a \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_compile/ClosedFam1.hs-boot b/testsuite/tests/indexed-types/should_compile/ClosedFam1.hs-boot new file mode 100644 index 0000000000000000000000000000000000000000..244e9d1a855b6b263e67a9ac1acad2f9b56fc564 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/ClosedFam1.hs-boot @@ -0,0 +1,7 @@ +{-# LANGUAGE TypeFamilies #-} + +module ClosedFam1 where + +type family Foo b where + Foo Int = Bool + Foo [different] = Maybe different \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_compile/ClosedFam2.hs b/testsuite/tests/indexed-types/should_compile/ClosedFam2.hs new file mode 100644 index 0000000000000000000000000000000000000000..c07c84eb6f25d65423d9a367a9c0e7aa8dad1e19 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/ClosedFam2.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies #-} + +module ClosedFam2 where + +import {-# SOURCE #-} ClosedFam2 + +type family Foo a where + Foo Int = Bool + Foo [a] = Maybe a \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_compile/ClosedFam2.hs-boot b/testsuite/tests/indexed-types/should_compile/ClosedFam2.hs-boot new file mode 100644 index 0000000000000000000000000000000000000000..f13bf46d6e47cf7fa59b37cbcc132b9a2739b033 --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/ClosedFam2.hs-boot @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeFamilies #-} + +module ClosedFam2 where + +type family Foo b where .. diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index a64c19b439092787a2cfb0367efcd491af9c18ed..6327e6e48c7480954e1832396cb29700cd222767 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -227,4 +227,8 @@ test('T8011', ['$MAKE -s --no-print-directory T8011']) test('T8018', normal, compile, ['']) -test('T8020', normal, compile, ['']) \ No newline at end of file +test('T8020', normal, compile, ['']) +test('ClosedFam1', extra_clean(['ClosedFam1.o-boot', 'ClosedFam1.hi-boot']), + multimod_compile, ['ClosedFam1', '-v0']) +test('ClosedFam2', extra_clean(['ClosedFam2.o-boot', 'ClosedFam2.hi-boot']), + multimod_compile, ['ClosedFam2', '-v0']) \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.hs b/testsuite/tests/indexed-types/should_fail/ClosedFam3.hs new file mode 100644 index 0000000000000000000000000000000000000000..27033b9fc7a42e8154eb22ca479cddf35e0126b4 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE TypeFamilies #-} + +module ClosedFam3 where + +import {-# SOURCE #-} ClosedFam3 + +type family Foo a where + Foo Int = Bool + Foo Double = Char + +type family Bar a where + Bar Int = Bool + Bar Double = Double + +type family Baz a where + Baz Int = Bool \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.hs-boot b/testsuite/tests/indexed-types/should_fail/ClosedFam3.hs-boot new file mode 100644 index 0000000000000000000000000000000000000000..0388084fa79cc43be36737c2f61d36327e11c74d --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.hs-boot @@ -0,0 +1,13 @@ +{-# LANGUAGE TypeFamilies, PolyKinds #-} + +module ClosedFam3 where + +type family Foo a where + Foo Int = Bool + +type family Bar a where + Bar Int = Bool + Bar Double = Char + +type family Baz (a :: k) where + Baz Int = Bool \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr new file mode 100644 index 0000000000000000000000000000000000000000..1edebd66629a43b45bf85da7a17f33e8ab129f28 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr @@ -0,0 +1,25 @@ + +ClosedFam3.hs-boot:5:13: + Type constructor ‛Foo’ has conflicting definitions in the module + and its hs-boot file + Main module: closed type family Foo a@N :: * where + Foo Int = Bool + Foo Double = Char + Boot file: closed type family Foo a@N :: * where Foo Int = Bool + +ClosedFam3.hs-boot:8:13: + Type constructor ‛Bar’ has conflicting definitions in the module + and its hs-boot file + Main module: closed type family Bar a@N :: * where + Bar Int = Bool + Bar Double = Double + Boot file: closed type family Bar a@N :: * where + Bar Int = Bool + Bar Double = Char + +ClosedFam3.hs-boot:12:13: + Type constructor ‛Baz’ has conflicting definitions in the module + and its hs-boot file + Main module: closed type family Baz a@N :: * where Baz Int = Bool + Boot file: closed type family Baz (k::BOX)@N (a::k)@N :: * where + Baz * Int = Bool diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam4.hs b/testsuite/tests/indexed-types/should_fail/ClosedFam4.hs new file mode 100644 index 0000000000000000000000000000000000000000..348278ecb29103a16164360e4fb0bf05011ea564 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam4.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE TypeFamilies #-} + +module ClosedFam4 where + +type family Foo a where .. \ No newline at end of file diff --git a/testsuite/tests/indexed-types/should_fail/ClosedFam4.stderr b/testsuite/tests/indexed-types/should_fail/ClosedFam4.stderr new file mode 100644 index 0000000000000000000000000000000000000000..34f8c9721e3f72101b9b506b39f8c5dd60bd3058 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/ClosedFam4.stderr @@ -0,0 +1,5 @@ + +ClosedFam4.hs:5:1: + You may omit the equations in a closed type family + only in a .hs-boot file + In the family declaration for ‛Foo’ diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index d14f3459802c0e908c5ead2ad18f3a6769332190..04d19abd16011c9a2dcf57850a16c8ef1828c13e 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -100,4 +100,8 @@ test('T7786', normal, compile_fail, ['']) test('NoGood', normal, compile_fail, ['']) test('T7967', normal, compile_fail, ['']) -test('T7938', normal, compile_fail, ['']) \ No newline at end of file +test('T7938', normal, compile_fail, ['']) + +test('ClosedFam3', extra_clean(['ClosedFam3.o-boot', 'ClosedFam3.hi-boot']), + multimod_compile_fail, ['ClosedFam3', '-v0']) +test('ClosedFam4', normal, compile_fail, ['']) \ No newline at end of file