[commit: testsuite] master: Test Trac #8155 (11eb77f)
git at git.haskell.org
git at git.haskell.org
Thu Aug 29 17:47:21 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/11eb77f7cb410dc76d982b731ffadb69116291ce/testsuite
>---------------------------------------------------------------
commit 11eb77f7cb410dc76d982b731ffadb69116291ce
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Wed Aug 28 16:40:44 2013 +0100
Test Trac #8155
>---------------------------------------------------------------
11eb77f7cb410dc76d982b731ffadb69116291ce
tests/indexed-types/should_fail/T8155.hs | 30 ++++++++++++++++++++++++++
tests/indexed-types/should_fail/T8155.stderr | 9 ++++++++
tests/indexed-types/should_fail/all.T | 1 +
3 files changed, 40 insertions(+)
diff --git a/tests/indexed-types/should_fail/T8155.hs b/tests/indexed-types/should_fail/T8155.hs
new file mode 100644
index 0000000..97f8961
--- /dev/null
+++ b/tests/indexed-types/should_fail/T8155.hs
@@ -0,0 +1,30 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE FlexibleInstances #-}
+
+module Test where
+
+
+data Vector a = Vector a
+data Matrix a = Matrix a
+
+class Build f where
+ build' :: BoundsOf f -> f -> ContainerOf f
+
+
+
+type family BoundsOf x where
+ BoundsOf (a->a->a) = (Int,Int)
+ BoundsOf (a->a) = Int
+
+type family ContainerOf x where
+ ContainerOf (a->a) = Vector a
+ ContainerOf (a->a->a) = Matrix a
+
+
+
+instance (Num a) => Build (a->a) where
+ build' = buildV
+
+
+buildV :: (Integral a, Num b) => a -> (b -> c) -> Vector c
+buildV _ _ = undefined
diff --git a/tests/indexed-types/should_fail/T8155.stderr b/tests/indexed-types/should_fail/T8155.stderr
new file mode 100644
index 0000000..c85b84b
--- /dev/null
+++ b/tests/indexed-types/should_fail/T8155.stderr
@@ -0,0 +1,9 @@
+
+T8155.hs:26:14:
+ Could not deduce (Integral (BoundsOf (a -> a)))
+ arising from a use of ‛buildV’
+ from the context (Num a)
+ bound by the instance declaration at T8155.hs:25:10-32
+ In the expression: buildV
+ In an equation for ‛build'’: build' = buildV
+ In the instance declaration for ‛Build (a -> a)’
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 14344da..68fb9ea 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -106,3 +106,4 @@ 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, [''])
+test('T8155', normal, compile_fail, [''])
More information about the ghc-commits
mailing list