[commit: ghc] master: Add regression tests for #12083 (01af8ae)
git at git.haskell.org
git at git.haskell.org
Fri May 12 13:08:14 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/01af8aee30c743ab505e164ac9aa02149fbe4b9e/ghc
>---------------------------------------------------------------
commit 01af8aee30c743ab505e164ac9aa02149fbe4b9e
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date: Fri May 12 08:54:30 2017 -0400
Add regression tests for #12083
Summary:
Commit 0c9d9dec0a924a4f34f4cff26d004143c028861a (the fix for #13271) fixed the
programs in #12083. This adds regression tests for them.
Test Plan: make test TEST="T12083a T12083b"
Reviewers: austin, bgamari
Subscribers: rwbarton, thomie
GHC Trac Issues: #12083
Differential Revision: https://phabricator.haskell.org/D3573
>---------------------------------------------------------------
01af8aee30c743ab505e164ac9aa02149fbe4b9e
testsuite/tests/typecheck/should_fail/T12083a.hs | 19 +++++++++++++++++++
testsuite/tests/typecheck/should_fail/T12083a.stderr | 12 ++++++++++++
testsuite/tests/typecheck/should_fail/T12083b.hs | 9 +++++++++
testsuite/tests/typecheck/should_fail/T12083b.stderr | 7 +++++++
testsuite/tests/typecheck/should_fail/all.T | 2 ++
5 files changed, 49 insertions(+)
diff --git a/testsuite/tests/typecheck/should_fail/T12083a.hs b/testsuite/tests/typecheck/should_fail/T12083a.hs
new file mode 100644
index 0000000..0ca86f7
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12083a.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE UnicodeSyntax #-}
+module T12803a where
+
+type Constrd a = Num a ⇒ a
+
+data ADT a = ADT (Constrd a) ExistentiallyLost
+
+data ExistentiallyLost = ∀ u. TC u ⇒ ExistentiallyLost u
+
+class u ~ (ATF1 u, ATF2 u) ⇒ TC u where
+ type ATF1 u ∷ *
+ type ATF2 u ∷ *
+ uie_handlers ∷ ADT Int
+
+-- Loop:
+-- - ADT depends on ExistentiallyLost (also the Constrd appendage)
+-- - ExistentiallyLost depends on TC
+-- - TC depends on ADT
diff --git a/testsuite/tests/typecheck/should_fail/T12083a.stderr b/testsuite/tests/typecheck/should_fail/T12083a.stderr
new file mode 100644
index 0000000..dc1452d
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12083a.stderr
@@ -0,0 +1,12 @@
+
+T12083a.hs:5:1: error:
+ • Illegal qualified type: Num a => a
+ Perhaps you intended to use RankNTypes or Rank2Types
+ • In the type synonym declaration for ‘Constrd’
+
+T12083a.hs:9:26: error:
+ • Data constructor ‘ExistentiallyLost’ has existential type variables, a context, or a specialised result type
+ ExistentiallyLost :: forall u. TC u => u -> ExistentiallyLost
+ (Use ExistentialQuantification or GADTs to allow this)
+ • In the definition of data constructor ‘ExistentiallyLost’
+ In the data type declaration for ‘ExistentiallyLost’
diff --git a/testsuite/tests/typecheck/should_fail/T12083b.hs b/testsuite/tests/typecheck/should_fail/T12083b.hs
new file mode 100644
index 0000000..3992db3
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12083b.hs
@@ -0,0 +1,9 @@
+{-# LANGUAGE GADTs #-}
+
+module T12083b where
+
+class Class a where
+ test :: a -> (Eq a => r) -> r
+
+data P a b where
+ Con :: (Class a, a ~ b) => P a b
diff --git a/testsuite/tests/typecheck/should_fail/T12083b.stderr b/testsuite/tests/typecheck/should_fail/T12083b.stderr
new file mode 100644
index 0000000..39ceece
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T12083b.stderr
@@ -0,0 +1,7 @@
+
+T12083b.hs:6:5: error:
+ • Illegal qualified type: Eq a => r
+ Perhaps you intended to use RankNTypes or Rank2Types
+ • When checking the class method:
+ test :: forall a. Class a => forall r. a -> (Eq a => r) -> r
+ In the class declaration for ‘Class’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 3875063..cf2c3c8 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -404,6 +404,8 @@ test('T12035', [], multimod_compile_fail, ['T12035', '-v0'])
test('T12035j', [extra_files(['T12035.hs', 'T12035a.hs', 'T12035.hs-boot']),
req_smp], multimod_compile_fail, ['T12035', '-j2 -v0'])
test('T12063', [expect_broken(12063)], multimod_compile_fail, ['T12063', '-v0'])
+test('T12083a', normal, compile_fail, [''])
+test('T12083b', normal, compile_fail, [''])
test('T11974b', normal, compile_fail, [''])
test('T12151', normal, compile_fail, [''])
test('T7437', normal, compile_fail, [''])
More information about the ghc-commits
mailing list