[commit: ghc] master: Test #10619 in typecheck/should_fail/T10619 (05e3541)
git at git.haskell.org
git at git.haskell.org
Sat Dec 26 21:02:49 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/05e35414219c29d2eaf4bb29b6dd6fb8a8388e9b/ghc
>---------------------------------------------------------------
commit 05e35414219c29d2eaf4bb29b6dd6fb8a8388e9b
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Sat Dec 26 13:55:42 2015 -0500
Test #10619 in typecheck/should_fail/T10619
>---------------------------------------------------------------
05e35414219c29d2eaf4bb29b6dd6fb8a8388e9b
testsuite/tests/typecheck/should_fail/T10619.hs | 20 ++++++
.../tests/typecheck/should_fail/T10619.stderr | 72 ++++++++++++++++++++++
testsuite/tests/typecheck/should_fail/all.T | 1 +
3 files changed, 93 insertions(+)
diff --git a/testsuite/tests/typecheck/should_fail/T10619.hs b/testsuite/tests/typecheck/should_fail/T10619.hs
new file mode 100644
index 0000000..d29c62f
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10619.hs
@@ -0,0 +1,20 @@
+{-# LANGUAGE RankNTypes #-}
+
+module T10619 where
+
+-- tests that type checking doesn't care about order. all of these
+-- should fail and be reported.
+
+foo _ = if True
+ then ((\x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ else \y -> y
+
+bar _ = if True
+ then \y -> y
+ else ((\x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+
+baz True = (\x -> x) :: (forall a. a -> a) -> forall b. b -> b
+baz False = \y -> y
+
+quux False = \y -> y
+quux True = (\x -> x) :: (forall a. a -> a) -> forall b. b -> b
diff --git a/testsuite/tests/typecheck/should_fail/T10619.stderr b/testsuite/tests/typecheck/should_fail/T10619.stderr
new file mode 100644
index 0000000..5ed7cfe
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10619.stderr
@@ -0,0 +1,72 @@
+
+T10619.hs:9:15: error:
+ • Couldn't match type ‘forall a. a -> a’ with ‘b -> b’
+ Expected type: (b -> b) -> b -> b
+ Actual type: (forall a. a -> a) -> b -> b
+ • In the expression:
+ ((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ In the expression:
+ if True then
+ ((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ else
+ \ y -> y
+ In an equation for ‘foo’:
+ foo _
+ = if True then
+ ((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ else
+ \ y -> y
+ • Relevant bindings include
+ foo :: r -> (b -> b) -> b -> b (bound at T10619.hs:8:1)
+
+T10619.hs:14:15: error:
+ • Couldn't match type ‘b’ with ‘a’
+ because type variable ‘a’ would escape its scope
+ This (rigid, skolem) type variable is bound by
+ a type expected by the context:
+ a -> a
+ at T10619.hs:14:15-65
+ Expected type: (b -> b) -> b -> b
+ Actual type: (forall a. a -> a) -> forall b. b -> b
+ • In the expression:
+ ((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ In the expression:
+ if True then
+ \ y -> y
+ else
+ ((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ In an equation for ‘bar’:
+ bar _
+ = if True then
+ \ y -> y
+ else
+ ((\ x -> x) :: (forall a. a -> a) -> forall b. b -> b)
+ • Relevant bindings include
+ bar :: r -> (b -> b) -> b -> b (bound at T10619.hs:12:1)
+
+T10619.hs:16:13: error:
+ • Couldn't match type ‘forall a. a -> a’ with ‘b -> b’
+ Expected type: (b -> b) -> b -> b
+ Actual type: (forall a. a -> a) -> b -> b
+ • In the expression:
+ (\ x -> x) :: (forall a. a -> a) -> forall b. b -> b
+ In an equation for ‘baz’:
+ baz True = (\ x -> x) :: (forall a. a -> a) -> forall b. b -> b
+ • Relevant bindings include
+ baz :: Bool -> (b -> b) -> b -> b (bound at T10619.hs:16:1)
+
+T10619.hs:20:14: error:
+ • Couldn't match type ‘b’ with ‘a’
+ because type variable ‘a’ would escape its scope
+ This (rigid, skolem) type variable is bound by
+ a type expected by the context:
+ a -> a
+ at T10619.hs:20:14-64
+ Expected type: (b -> b) -> b -> b
+ Actual type: (forall a. a -> a) -> forall b. b -> b
+ • In the expression:
+ (\ x -> x) :: (forall a. a -> a) -> forall b. b -> b
+ In an equation for ‘quux’:
+ quux True = (\ x -> x) :: (forall a. a -> a) -> forall b. b -> b
+ • Relevant bindings include
+ quux :: Bool -> (b -> b) -> b -> b (bound at T10619.hs:19:1)
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index aa43cce..4279950 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -397,3 +397,4 @@ test('CustomTypeErrors03', normal, compile_fail, [''])
test('T11112', normal, compile_fail, [''])
test('ClassOperator', normal, compile_fail, [''])
test('T11274', normal, compile_fail, [''])
+test('T10619', normal, compile_fail, [''])
More information about the ghc-commits
mailing list