Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ddd1c8b07ece78bbd56da5341e85d04bc07f7d3f

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

commit ddd1c8b07ece78bbd56da5341e85d04bc07f7d3f
Author: Ian Lynagh <i...@well-typed.com>
Date:   Wed Nov 28 02:40:18 2012 +0000

    Add a test for #7453

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

 tests/typecheck/should_fail/T7453.hs     |   32 +++++++++++++++++
 tests/typecheck/should_fail/T7453.stderr |   55 ++++++++++++++++++++++++++++++
 tests/typecheck/should_fail/all.T        |    1 +
 3 files changed, 88 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_fail/T7453.hs 
b/tests/typecheck/should_fail/T7453.hs
new file mode 100644
index 0000000..b79ac9a
--- /dev/null
+++ b/tests/typecheck/should_fail/T7453.hs
@@ -0,0 +1,32 @@
+
+module T7453 where
+
+newtype Id a = Id { runId :: a }
+
+-- cast1 :: a -> b
+cast1 v = runId z
+    where z :: Id t
+          z = aux
+              where aux = Id v
+
+-- cast2 :: a -> b
+cast2 v = z ()
+    where z :: () -> t
+          z = aux
+              where aux = const v
+
+-- cast3 :: a -> b
+cast3 v = z
+    where z :: t
+          z = v
+              where aux = const v
+
+cast1' :: a -> b
+cast1' = cast1
+
+cast2' :: a -> b
+cast2' = cast2
+
+cast3' :: a -> b
+cast3' = cast3
+
diff --git a/tests/typecheck/should_fail/T7453.stderr 
b/tests/typecheck/should_fail/T7453.stderr
new file mode 100644
index 0000000..af88fef
--- /dev/null
+++ b/tests/typecheck/should_fail/T7453.stderr
@@ -0,0 +1,55 @@
+
+T7453.hs:10:30:
+    Couldn't match expected type `t1' with actual type `t'
+      because type variable `t1' would escape its scope
+    This (rigid, skolem) type variable is bound by
+      the type signature for z :: Id t1
+      at T7453.hs:8:16-19
+    Relevant bindings include
+      cast1 :: t -> a (bound at T7453.hs:7:1)
+      v :: t (bound at T7453.hs:7:7)
+      z :: Id t1 (bound at T7453.hs:9:11)
+      aux :: Id t1 (bound at T7453.hs:10:21)
+    In the first argument of `Id', namely `v'
+    In the expression: Id v
+    In an equation for `aux': aux = Id v
+
+T7453.hs:16:33:
+    Couldn't match expected type `t2' with actual type `t'
+      because type variable `t2' would escape its scope
+    This (rigid, skolem) type variable is bound by
+      the type signature for z :: () -> t2
+      at T7453.hs:14:16-22
+    Relevant bindings include
+      cast2 :: t -> t1 (bound at T7453.hs:13:1)
+      v :: t (bound at T7453.hs:13:7)
+      z :: () -> t2 (bound at T7453.hs:15:11)
+      aux :: b -> t2 (bound at T7453.hs:16:21)
+    In the first argument of `const', namely `v'
+    In the expression: const v
+    In an equation for `aux': aux = const v
+
+T7453.hs:21:15:
+    Couldn't match expected type `t2' with actual type `t'
+      because type variable `t2' would escape its scope
+    This (rigid, skolem) type variable is bound by
+      the type signature for z :: t2
+      at T7453.hs:20:16
+    Relevant bindings include
+      cast3 :: t -> t1 (bound at T7453.hs:19:1)
+      v :: t (bound at T7453.hs:19:7)
+      z :: t2 (bound at T7453.hs:21:11)
+      aux :: forall b. b -> t2 (bound at T7453.hs:22:21)
+    In the expression: v
+    In an equation for `z':
+        z = v
+          where
+              aux = const v
+    In an equation for `cast3':
+        cast3 v
+          = z
+          where
+              z :: t
+              z = v
+                where
+                    aux = const v
diff --git a/tests/typecheck/should_fail/all.T 
b/tests/typecheck/should_fail/all.T
index 7187d90..9704f18 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -288,3 +288,4 @@ test('T7264', normal, compile_fail, [''])
 test('T6069', normal, compile_fail, [''])
 test('T7220', normal, compile_fail, [''])
 test('T7410', normal, compile_fail, [''])
+test('T7453', normal, compile_fail, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to