[commit: ghc] master: Test Trac #11192 (602889a)
git at git.haskell.org
git at git.haskell.org
Thu Dec 10 10:16:01 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/602889aa23daecc21caaecb99ae8b055bca191f6/ghc
>---------------------------------------------------------------
commit 602889aa23daecc21caaecb99ae8b055bca191f6
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Dec 10 10:15:16 2015 +0000
Test Trac #11192
>---------------------------------------------------------------
602889aa23daecc21caaecb99ae8b055bca191f6
.../tests/partial-sigs/should_compile/T11192.hs | 15 ++++++++
.../partial-sigs/should_compile/T11192.stderr | 44 ++++++++++++++++++++++
testsuite/tests/partial-sigs/should_compile/all.T | 1 +
3 files changed, 60 insertions(+)
diff --git a/testsuite/tests/partial-sigs/should_compile/T11192.hs b/testsuite/tests/partial-sigs/should_compile/T11192.hs
new file mode 100644
index 0000000..fb27a35
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_compile/T11192.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE PartialTypeSignatures #-}
+
+module T11192 where
+
+fails :: a
+fails =
+ let go :: _
+ go 0 a = a
+ in go (0 :: Int) undefined
+
+succeeds :: a
+succeeds =
+ let go :: _
+ go _ a = a
+ in go (0 :: Int) undefined
diff --git a/testsuite/tests/partial-sigs/should_compile/T11192.stderr b/testsuite/tests/partial-sigs/should_compile/T11192.stderr
new file mode 100644
index 0000000..2fac5eb
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_compile/T11192.stderr
@@ -0,0 +1,44 @@
+
+T11192.hs:7:14: warning:
+ • Found type wildcard ‘_’ standing for ‘Int -> t -> t’
+ Where: ‘t’ is a rigid type variable bound by
+ the inferred type of go :: Int -> t -> t at T11192.hs:8:8
+ • In the type signature:
+ go :: _
+ In the expression:
+ let
+ go :: _
+ go 0 a = a
+ in go (0 :: Int) undefined
+ In an equation for ‘fails’:
+ fails
+ = let
+ go :: _
+ go 0 a = a
+ in go (0 :: Int) undefined
+ • Relevant bindings include
+ go :: Int -> t -> t (bound at T11192.hs:8:8)
+ fails :: a (bound at T11192.hs:6:1)
+
+T11192.hs:13:14: warning:
+ • Found type wildcard ‘_’ standing for ‘t -> t1 -> t1’
+ Where: ‘t’ is a rigid type variable bound by
+ the inferred type of go :: t -> t1 -> t1 at T11192.hs:14:8
+ ‘t1’ is a rigid type variable bound by
+ the inferred type of go :: t -> t1 -> t1 at T11192.hs:14:8
+ • In the type signature:
+ go :: _
+ In the expression:
+ let
+ go :: _
+ go _ a = a
+ in go (0 :: Int) undefined
+ In an equation for ‘succeeds’:
+ succeeds
+ = let
+ go :: _
+ go _ a = a
+ in go (0 :: Int) undefined
+ • Relevant bindings include
+ go :: t -> t1 -> t1 (bound at T11192.hs:14:8)
+ succeeds :: a (bound at T11192.hs:12:1)
diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T
index 5567ef1..caa8934 100644
--- a/testsuite/tests/partial-sigs/should_compile/all.T
+++ b/testsuite/tests/partial-sigs/should_compile/all.T
@@ -58,3 +58,4 @@ test('T10519', normal, compile, [''])
test('T10463', normal, compile, [''])
test('ExprSigLocal', normal, compile, [''])
test('T11016', normal, compile, [''])
+test('T11192', normal, compile, [''])
More information about the ghc-commits
mailing list