[commit: testsuite] master: Add regression test for #8142 (0158d71)

git at git.haskell.org git at git.haskell.org
Mon Aug 19 14:44:28 CEST 2013


Repository : ssh://git@git.haskell.org/testsuite

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/0158d71a121007f0de35ba7b94f255fc79f0f59f/testsuite

>---------------------------------------------------------------

commit 0158d71a121007f0de35ba7b94f255fc79f0f59f
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Mon Aug 19 13:44:04 2013 +0100

    Add regression test for #8142


>---------------------------------------------------------------

0158d71a121007f0de35ba7b94f255fc79f0f59f
 tests/typecheck/should_fail/T8142.hs     |   11 +++++++++++
 tests/typecheck/should_fail/T8142.stderr |   23 +++++++++++++++++++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 35 insertions(+)

diff --git a/tests/typecheck/should_fail/T8142.hs b/tests/typecheck/should_fail/T8142.hs
new file mode 100644
index 0000000..fb523fb
--- /dev/null
+++ b/tests/typecheck/should_fail/T8142.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module T8142 where
+
+tracer :: (Functor f, Coinductive f) => (c -> f c) -> (c -> f c)
+tracer = h where h = (\(_, b) -> ((outI . fmap h) b)) . out
+
+class Functor g => Coinductive g where
+  type Nu g :: *
+  out     :: Nu g -> g (Nu g)
+  outI    :: g (Nu g) -> Nu g
diff --git a/tests/typecheck/should_fail/T8142.stderr b/tests/typecheck/should_fail/T8142.stderr
new file mode 100644
index 0000000..22c5d64
--- /dev/null
+++ b/tests/typecheck/should_fail/T8142.stderr
@@ -0,0 +1,23 @@
+
+T8142.hs:6:18:
+    Couldn't match type ‛Nu f0’ with ‛Nu f’
+    NB: ‛Nu’ is a type function, and may not be injective
+    The type variable ‛f0’ is ambiguous
+    Expected type: a -> Nu f
+      Actual type: a -> Nu f0
+    When checking that ‛h’
+      has the inferred type ‛forall (f :: * -> *) a. a -> Nu f’
+    Probable cause: the inferred type is ambiguous
+    In an equation for ‛tracer’:
+        tracer
+          = h
+          where
+              h = (\ (_, b) -> ((outI . fmap h) b)) . out
+
+T8142.hs:6:57:
+    Occurs check: cannot construct the infinite type: a ~ f1 a
+    Expected type: a -> (t0, f1 a)
+      Actual type: Nu ((,) t0) -> (t0, Nu ((,) t0))
+    Relevant bindings include h :: a -> Nu f1 (bound at T8142.hs:6:18)
+    In the second argument of ‛(.)’, namely ‛out’
+    In the expression: (\ (_, b) -> ((outI . fmap h) b)) . out
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index b6d184c..b2d9bf1 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -311,3 +311,4 @@ test('T7869', normal, compile_fail, [''])
 test('T7892', normal, compile_fail, [''])
 test('T7809', normal, compile_fail, [''])
 test('T7989', normal, compile_fail, [''])
+test('T8142', normal, compile_fail, [''])





More information about the ghc-commits mailing list