[commit: testsuite] master: Test Trac #8227 (309e564)
git at git.haskell.org
git at git.haskell.org
Tue Sep 10 18:58:41 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/309e564d93e98f7051a8f37fd463d52ec550016a/testsuite
>---------------------------------------------------------------
commit 309e564d93e98f7051a8f37fd463d52ec550016a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Fri Sep 6 10:02:55 2013 +0100
Test Trac #8227
>---------------------------------------------------------------
309e564d93e98f7051a8f37fd463d52ec550016a
tests/indexed-types/should_fail/Makefile | 4 +++
tests/indexed-types/should_fail/T8227.hs | 37 ++++++++++++++++++++++++++
tests/indexed-types/should_fail/T8227.stderr | 7 +++++
tests/indexed-types/should_fail/T8227a.hs | 7 +++++
tests/indexed-types/should_fail/all.T | 4 +++
5 files changed, 59 insertions(+)
diff --git a/tests/indexed-types/should_fail/Makefile b/tests/indexed-types/should_fail/Makefile
index 7c2b8d1..dfd8b18 100644
--- a/tests/indexed-types/should_fail/Makefile
+++ b/tests/indexed-types/should_fail/Makefile
@@ -5,3 +5,7 @@ include $(TOP)/mk/test.mk
T7354a:
'$(TEST_HC)' $(TEST_HC_OPTS) -c T7354b.hs
-'$(TEST_HC)' $(TEST_HC_OPTS) -c T7354a.hs
+
+T8227:
+ '$(TEST_HC)' $(TEST_HC_OPTS) -c T8227a.hs
+ -'$(TEST_HC)' $(TEST_HC_OPTS) -c T8227.hs
diff --git a/tests/indexed-types/should_fail/T8227.hs b/tests/indexed-types/should_fail/T8227.hs
new file mode 100644
index 0000000..69471db
--- /dev/null
+++ b/tests/indexed-types/should_fail/T8227.hs
@@ -0,0 +1,37 @@
+{-# LANGUAGE TypeFamilies #-}
+module T8227
+ (
+ absoluteToParam
+ ) where
+
+import T8227a
+
+type family Scalar a :: *
+type instance Scalar (a -> v) = a -> Scalar v
+
+arcLengthToParam :: Scalar (V p) -> p -> Scalar (V p) -> Scalar (V p)
+arcLengthToParam = undefined
+
+absoluteToParam :: Scalar (V a) -> a -> Scalar (V a)
+absoluteToParam eps seg = arcLengthToParam eps eps
+
+{-
+
+Scalar (V a) ~ Scalar (V p0)
+Scalar (V a) ~ p0
+Scalar (V a) ~ Scalar (V p0) -> Scalar (V p0)
+
+
+Scalar (V a) ~ t0
+Scalar (V p0) ~ t0
+Scalar (V a) ~ p0
+Scalar (V a) ~ t0 -> t0
+
+Scalar (V a) ~ t0
+Scalar (V t0) ~ t0
+Scalar (V a) ~ t0 -> t0
+
+
+-}
+
+
diff --git a/tests/indexed-types/should_fail/T8227.stderr b/tests/indexed-types/should_fail/T8227.stderr
new file mode 100644
index 0000000..fdcbc41
--- /dev/null
+++ b/tests/indexed-types/should_fail/T8227.stderr
@@ -0,0 +1,7 @@
+
+T8227.hs:16:44:
+ Occurs check: cannot construct the infinite type: t0 ~ t0 -> t0
+ Expected type: Scalar (V (t0 -> t0))
+ Actual type: Scalar (V a)
+ In the first argument of ‛arcLengthToParam’, namely ‛eps’
+ In the expression: arcLengthToParam eps eps
diff --git a/tests/indexed-types/should_fail/T8227a.hs b/tests/indexed-types/should_fail/T8227a.hs
new file mode 100644
index 0000000..157d4bd
--- /dev/null
+++ b/tests/indexed-types/should_fail/T8227a.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE TypeFamilies #-}
+module T8227a where
+
+type family V a :: *
+
+type instance V Double = Double
+type instance V (a -> b) = V b
\ No newline at end of file
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 68fb9ea..5e48e4a 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -107,3 +107,7 @@ 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, [''])
+test('T8227',
+ extra_clean(['T8227a.o', 'T8227a.hi']),
+ run_command,
+ ['$MAKE -s --no-print-directory T8227'])
More information about the ghc-commits
mailing list