[commit: ghc] master: Add regression tests for #10045, #10999 (f86fb5e)
git at git.haskell.org
git at git.haskell.org
Tue Oct 27 13:25:17 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f86fb5e5a0694ea57cace824bbc0dce06bdf0698/ghc
>---------------------------------------------------------------
commit f86fb5e5a0694ea57cace824bbc0dce06bdf0698
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Oct 22 16:04:39 2015 +0100
Add regression tests for #10045, #10999
>---------------------------------------------------------------
f86fb5e5a0694ea57cace824bbc0dce06bdf0698
testsuite/tests/partial-sigs/should_fail/T10045.hs | 8 ++++++++
.../tests/partial-sigs/should_fail/T10045.stderr | 24 ++++++++++++++++++++++
testsuite/tests/partial-sigs/should_fail/T10999.hs | 8 ++++++++
.../should_fail/T10999.stderr} | 0
testsuite/tests/partial-sigs/should_fail/all.T | 2 ++
5 files changed, 42 insertions(+)
diff --git a/testsuite/tests/partial-sigs/should_fail/T10045.hs b/testsuite/tests/partial-sigs/should_fail/T10045.hs
new file mode 100644
index 0000000..9b8c45f
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T10045.hs
@@ -0,0 +1,8 @@
+module T10045 where
+
+newtype Meta = Meta ()
+
+foo (Meta ws1) =
+ let copy :: _
+ copy w from = copy w True
+ in copy ws1 False
diff --git a/testsuite/tests/partial-sigs/should_fail/T10045.stderr b/testsuite/tests/partial-sigs/should_fail/T10045.stderr
new file mode 100644
index 0000000..c57170e
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T10045.stderr
@@ -0,0 +1,24 @@
+
+T10045.hs:6:18: error:
+ Found type wildcard ‘_’ standing for ‘t1 -> Bool -> t2’
+ Where: ‘t1’ is a rigid type variable bound by
+ the inferred type of copy :: t1 -> Bool -> t2 at T10045.hs:7:10
+ ‘t2’ is a rigid type variable bound by
+ the inferred type of copy :: t1 -> Bool -> t2 at T10045.hs:7:10
+ To use the inferred type, enable PartialTypeSignatures
+ Relevant bindings include
+ ws1 :: () (bound at T10045.hs:5:11)
+ foo :: Meta -> t (bound at T10045.hs:5:1)
+ In the type signature for:
+ copy :: _
+ In the expression:
+ let
+ copy :: _
+ copy w from = copy w True
+ in copy ws1 False
+ In an equation for ‘foo’:
+ foo (Meta ws1)
+ = let
+ copy :: _
+ copy w from = copy w True
+ in copy ws1 False
diff --git a/testsuite/tests/partial-sigs/should_fail/T10999.hs b/testsuite/tests/partial-sigs/should_fail/T10999.hs
new file mode 100644
index 0000000..07d86ff
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T10999.hs
@@ -0,0 +1,8 @@
+module T10999 where
+
+import qualified Data.Set as Set
+
+f :: () -> _
+f _ = Set.fromList undefined
+
+g = map fst $ Set.toList $ f ()
diff --git a/testsuite/tests/deSugar/should_run/T5472.stdout b/testsuite/tests/partial-sigs/should_fail/T10999.stderr
similarity index 100%
copy from testsuite/tests/deSugar/should_run/T5472.stdout
copy to testsuite/tests/partial-sigs/should_fail/T10999.stderr
diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T
index d172a01..bebd8bd 100644
--- a/testsuite/tests/partial-sigs/should_fail/all.T
+++ b/testsuite/tests/partial-sigs/should_fail/all.T
@@ -59,4 +59,6 @@ test('WildcardInTypeFamilyInstanceRHS', normal, compile_fail, [''])
test('WildcardInTypeSynonymLHS', normal, compile_fail, [''])
test('WildcardInTypeSynonymRHS', normal, compile_fail, [''])
test('T10615', normal, compile_fail, [''])
+test('T10045', normal, compile_fail, [''])
+test('T10999', normal, compile_fail, [''])
More information about the ghc-commits
mailing list