diff --git a/testsuite/tests/polykinds/T5938.hs b/testsuite/tests/polykinds/T5938.hs new file mode 100644 index 0000000000000000000000000000000000000000..bde1e7453e811616640a2353508fa61419639014 --- /dev/null +++ b/testsuite/tests/polykinds/T5938.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE PolyKinds, TypeFamilies, DataKinds #-} +module T5938 where + +type family KindFam a +type instance KindFam (a :: *) = Int +type instance KindFam (a :: Bool) = Bool +type instance KindFam (a :: Maybe k) = Char -- doesn't work diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index e8064f1db669e03df6da9a39b63552619142e7f5..3676c8de4df515110718c5d8fc19fb7aed3636c7 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -31,4 +31,5 @@ test('T5881', normal, run_command, ['$MAKE -s --no-print-directory T5881']) test('T5716', normal, compile_fail, ['']) test('T5937', normal, compile, ['']) test('T5935', normal, compile, ['']) +test('T5938', normal, compile, ['']) test('T5948', normal, compile, ['']) diff --git a/testsuite/tests/simplCore/should_compile/rule2.stderr b/testsuite/tests/simplCore/should_compile/rule2.stderr index 8279fce14f6a406f001d938acd8e8e5e6f372029..0fd629d9695673b6c0073fe21d27a5d164b5e2c6 100644 --- a/testsuite/tests/simplCore/should_compile/rule2.stderr +++ b/testsuite/tests/simplCore/should_compile/rule2.stderr @@ -1,30 +1,30 @@ - -==================== FloatOut stats: ==================== -1 Lets floated to top level; 0 Lets floated elsewhere; from 4 Lambda groups - - - -==================== FloatOut stats: ==================== -0 Lets floated to top level; 0 Lets floated elsewhere; from 3 Lambda groups - - - -==================== Grand total simplifier statistics ==================== -Total ticks: 11 - -2 PreInlineUnconditionally - 1 f - 1 lvl -1 UnfoldingDone 1 Roman.bar -1 RuleFired 1 foo/bar -7 BetaReduction - 1 f - 1 m - 1 a - 1 b - 1 m - 1 m - 1 a -8 SimplifierDone 8 - - + +==================== FloatOut stats: ==================== +1 Lets floated to top level; 0 Lets floated elsewhere; from 4 Lambda groups + + + +==================== FloatOut stats: ==================== +0 Lets floated to top level; 0 Lets floated elsewhere; from 3 Lambda groups + + + +==================== Grand total simplifier statistics ==================== +Total ticks: 11 + +2 PreInlineUnconditionally + 1 f + 1 lvl +1 UnfoldingDone 1 Roman.bar +1 RuleFired 1 foo/bar +7 BetaReduction + 1 f + 1 m + 1 a + 1 m + 1 b + 1 m + 1 a +8 SimplifierDone 8 + + diff --git a/testsuite/tests/typecheck/should_compile/T6011.hs b/testsuite/tests/typecheck/should_compile/T6011.hs new file mode 100644 index 0000000000000000000000000000000000000000..867d69b2fd60614183b6e768b01264b7b19693ea --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T6011.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE DataKinds, FlexibleInstances, ScopedTypeVariables, TypeFamilies #-} + +module T6011 where + +data family GenMod :: Modulus * -> * -> * + +type Mod n = GenMod (FiniteRing n) Integer + +data Modulus n = FiniteRing n + +data instance GenMod (FiniteRing n) Integer = Mod Integer Integer diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 918d5c8c2ee9f3f7d2a1d9b8d53d5afb58c3b48c..bccb1fa550851f987a57e373729fdf42c0c63c96 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -376,4 +376,5 @@ test('T3108', normal, compile, ['']) test('T5792',normal,run_command, ['$MAKE -s --no-print-directory T5792']) -test('PolytypeDecomp', normal, compile, ['']) \ No newline at end of file +test('PolytypeDecomp', normal, compile, ['']) +test('T6011', normal, compile, ['']) diff --git a/testsuite/tests/typecheck/should_compile/tc141.stderr b/testsuite/tests/typecheck/should_compile/tc141.stderr index 0d083033458b24d8fe5e022995bab35520e0a252..db8448f464c03cf64c6b565e066fe7691c63a002 100644 --- a/testsuite/tests/typecheck/should_compile/tc141.stderr +++ b/testsuite/tests/typecheck/should_compile/tc141.stderr @@ -1,43 +1,43 @@ - -tc141.hs:11:12: - You cannot bind scoped type variable `a' - in a pattern binding signature - In the pattern: p :: a - In the pattern: (p :: a, q :: a) - In a pattern binding: (p :: a, q :: a) = x - -tc141.hs:11:31: - Couldn't match expected type `a1' with actual type `a' - `a1' is a rigid type variable bound by - an expression type signature: a1 at tc141.hs:11:31 - `a' is a rigid type variable bound by - the inferred type of f :: (a, a) -> (t, a) at tc141.hs:11:1 - In the expression: q :: a - In the expression: (q :: a, p) - In the expression: let (p :: a, q :: a) = x in (q :: a, p) - -tc141.hs:13:13: - You cannot bind scoped type variable `a' - in a pattern binding signature - In the pattern: y :: a - In a pattern binding: y :: a = a - In the expression: - let y :: a = a in - let - v :: a - v = b - in v - -tc141.hs:15:18: - Couldn't match expected type `a1' with actual type `t1' - `a1' is a rigid type variable bound by - the type signature for v :: a1 at tc141.hs:14:19 - `t1' is a rigid type variable bound by - the inferred type of g :: t -> t1 -> a at tc141.hs:13:1 - In the expression: b - In an equation for `v': v = b - In the expression: - let - v :: a - v = b - in v + +tc141.hs:11:12: + You cannot bind scoped type variable `a' + in a pattern binding signature + In the pattern: p :: a + In the pattern: (p :: a, q :: a) + In a pattern binding: (p :: a, q :: a) = x + +tc141.hs:11:31: + Couldn't match expected type `a1' with actual type `a' + `a1' is a rigid type variable bound by + an expression type signature: a1 at tc141.hs:11:31 + `a' is a rigid type variable bound by + the inferred type of f :: (a, a) -> (t, a) at tc141.hs:11:1 + In the expression: q :: a + In the expression: (q :: a, p) + In the expression: let (p :: a, q :: a) = x in (q :: a, p) + +tc141.hs:13:13: + You cannot bind scoped type variable `a' + in a pattern binding signature + In the pattern: y :: a + In a pattern binding: y :: a = a + In the expression: + let y :: a = a in + let + v :: a + v = b + in v + +tc141.hs:15:18: + Couldn't match expected type `a2' with actual type `t' + `a2' is a rigid type variable bound by + the type signature for v :: a2 at tc141.hs:14:19 + `t' is a rigid type variable bound by + the inferred type of g :: a -> t -> a1 at tc141.hs:13:1 + In the expression: b + In an equation for `v': v = b + In the expression: + let + v :: a + v = b + in v