[commit: testsuite] master: Test Trac #8566 (a6e35a0)
git at git.haskell.org
git at git.haskell.org
Tue Dec 10 17:54:26 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/a6e35a07d6d48ce782c5473c03cc09da996e1986/testsuite
>---------------------------------------------------------------
commit a6e35a07d6d48ce782c5473c03cc09da996e1986
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Tue Dec 10 17:53:46 2013 +0000
Test Trac #8566
>---------------------------------------------------------------
a6e35a07d6d48ce782c5473c03cc09da996e1986
tests/polykinds/T8566.hs | 31 +++++++++++++++++++++++++++++++
tests/polykinds/T8566.stderr | 18 ++++++++++++++++++
tests/polykinds/all.T | 1 +
3 files changed, 50 insertions(+)
diff --git a/tests/polykinds/T8566.hs b/tests/polykinds/T8566.hs
new file mode 100644
index 0000000..ee5892c
--- /dev/null
+++ b/tests/polykinds/T8566.hs
@@ -0,0 +1,31 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeOperators #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+
+module T8566 where
+
+data U (s :: *) = forall v. AA v [U s]
+-- AA :: forall (s:*) (v:*). v -> [U s] -> U s
+
+data I (u :: U *) (r :: [*]) :: * where
+ A :: I (AA t as) r -- Existential k
+
+-- A :: forall (u:U *) (r:[*]) Universal
+-- (k:BOX) (t:k) (as:[U *]). Existential
+-- (u ~ AA * k t as) =>
+-- I u r
+
+-- fs unused, but needs to be present for the bug
+class C (u :: U *) (r :: [*]) (fs :: [*]) where
+ c :: I u r -> I u r
+
+-- c :: forall (u :: U *) (r :: [*]) (fs :: [*]). C u r fs => I u r -> I u r
+
+instance (C (AA (t (I a ps)) as) ps fs) => C (AA t (a ': as)) ps fs where
+-- instance C (AA t (a ': as)) ps fs where
+ c A = c undefined
diff --git a/tests/polykinds/T8566.stderr b/tests/polykinds/T8566.stderr
new file mode 100644
index 0000000..639f72b
--- /dev/null
+++ b/tests/polykinds/T8566.stderr
@@ -0,0 +1,18 @@
+
+T8566.hs:31:9:
+ Could not deduce (C ('AA (t (I a ps)) as) ps fs0)
+ arising from a use of ‛c’
+ from the context (C ('AA (t (I a ps)) as) ps fs)
+ bound by the instance declaration at T8566.hs:29:10-67
+ or from ('AA t (a : as) ~ 'AA t1 as1)
+ bound by a pattern with constructor
+ A :: forall (r :: [*]) (t :: k) (as :: [U *]). I ('AA t as) r,
+ in an equation for ‛c’
+ at T8566.hs:31:5
+ The type variable ‛fs0’ is ambiguous
+ Relevant bindings include
+ c :: I ('AA t (a : as)) ps -> I ('AA t (a : as)) ps
+ (bound at T8566.hs:31:3)
+ In the expression: c undefined
+ In an equation for ‛c’: c A = c undefined
+ In the instance declaration for ‛C ('AA t (a : as)) ps fs’
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index 44edefb..2d53e04 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -94,3 +94,4 @@ test('T8359', normal, compile, [''])
test('T8391', normal, compile, [''])
test('T8449', normal, run_command, ['$MAKE -s --no-print-directory T8449'])
test('T8534', normal, compile, [''])
+test('T8566', normal, compile_fail,[''])
More information about the ghc-commits
mailing list