[commit: ghc] master: Add test for T11122 (d6b91ea)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 17:33:28 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/d6b91ea62e974969f203857deaa60f743e42513a/ghc
>---------------------------------------------------------------
commit d6b91ea62e974969f203857deaa60f743e42513a
Author: Ben Gamari <bgamari.foss at gmail.com>
Date: Fri Dec 18 17:22:15 2015 +0100
Add test for T11122
Test Plan: validate
Reviewers: austin
Subscribers: thomie
Differential Revision: https://phabricator.haskell.org/D1655
GHC Trac Issues: #11122
>---------------------------------------------------------------
d6b91ea62e974969f203857deaa60f743e42513a
testsuite/tests/partial-sigs/should_fail/T11122.hs | 28 ++++++++++++++++++++++
.../tests/partial-sigs/should_fail/T11122.stderr | 7 ++++++
testsuite/tests/partial-sigs/should_fail/all.T | 2 +-
3 files changed, 36 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/partial-sigs/should_fail/T11122.hs b/testsuite/tests/partial-sigs/should_fail/T11122.hs
new file mode 100644
index 0000000..5cf104d
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T11122.hs
@@ -0,0 +1,28 @@
+{-# LANGUAGE NoMonomorphismRestriction #-}
+{-# LANGUAGE PartialTypeSignatures #-}
+
+module T11122 where
+
+data Parser a
+
+instance Functor Parser where
+ fmap = undefined
+
+many p = undefined
+
+digit = undefined
+
+parseTest = undefined
+
+--------------------------------------------
+
+parser :: Parser _
+--parser :: Parser Int
+parser = read <$> many digit
+
+data Wrapper = Wrapper Int deriving Show
+
+wrapperParser = Wrapper <$> parser
+
+main :: IO ()
+main = parseTest wrapperParser "0"
diff --git a/testsuite/tests/partial-sigs/should_fail/T11122.stderr b/testsuite/tests/partial-sigs/should_fail/T11122.stderr
new file mode 100644
index 0000000..57a74f9
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T11122.stderr
@@ -0,0 +1,7 @@
+
+T11122.hs:19:18: warning:
+ • Found type wildcard ‘_’ standing for ‘Int’
+ • In the type signature:
+ parser :: Parser _
+ • Relevant bindings include
+ parser :: Parser Int (bound at T11122.hs:21:1)
diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T
index dbbe946..2cb65f0 100644
--- a/testsuite/tests/partial-sigs/should_fail/all.T
+++ b/testsuite/tests/partial-sigs/should_fail/all.T
@@ -60,4 +60,4 @@ test('WildcardInTypeSynonymRHS', normal, compile_fail, [''])
test('T10615', normal, compile_fail, [''])
test('T10045', normal, compile_fail, [''])
test('T10999', normal, compile_fail, [''])
-
+test('T11122', normal, compile, [''])
\ No newline at end of file
More information about the ghc-commits
mailing list