[commit: ghc] master: Test Trac #10438 (b2b69b2)

git at git.haskell.org git at git.haskell.org
Tue Jun 2 11:43:37 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b2b69b2a31e5d41210e851687887377072afd020/ghc

>---------------------------------------------------------------

commit b2b69b2a31e5d41210e851687887377072afd020
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Jun 2 12:43:11 2015 +0100

    Test Trac #10438


>---------------------------------------------------------------

b2b69b2a31e5d41210e851687887377072afd020
 .../tests/partial-sigs/should_compile/T10438.hs    |  8 +++++++
 .../partial-sigs/should_compile/T10438.stderr      | 26 ++++++++++++++++++++++
 testsuite/tests/partial-sigs/should_compile/all.T  |  1 +
 3 files changed, 35 insertions(+)

diff --git a/testsuite/tests/partial-sigs/should_compile/T10438.hs b/testsuite/tests/partial-sigs/should_compile/T10438.hs
new file mode 100644
index 0000000..583e0dd
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_compile/T10438.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE PartialTypeSignatures #-}
+{-# LANGUAGE TypeFamilies #-}
+module T10438 where
+
+foo f = g
+  where g r = x
+          where x :: _
+                x = r
diff --git a/testsuite/tests/partial-sigs/should_compile/T10438.stderr b/testsuite/tests/partial-sigs/should_compile/T10438.stderr
new file mode 100644
index 0000000..9133a56
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_compile/T10438.stderr
@@ -0,0 +1,26 @@
+
+T10438.hs:7:22: warning:
+    Found hole ‘_’ with type: w_1
+    Where: ‘w_1’ is a rigid type variable bound by
+                 the inferred type of g :: w_1 -> w_1 at T10438.hs:6:9
+    Relevant bindings include
+      r :: w_1 (bound at T10438.hs:6:11)
+      g :: w_1 -> w_1 (bound at T10438.hs:6:9)
+      f :: t (bound at T10438.hs:5:5)
+      foo :: t -> w_ -> w_ (bound at T10438.hs:5:1)
+    In the type signature for ‘x’: _
+    In an equation for ‘g’:
+        g r
+          = x
+          where
+              x :: _
+              x = r
+    In an equation for ‘foo’:
+        foo f
+          = g
+          where
+              g r
+                = x
+                where
+                    x :: _
+                    x = r
diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T
index 91294a5..812ff0a 100644
--- a/testsuite/tests/partial-sigs/should_compile/all.T
+++ b/testsuite/tests/partial-sigs/should_compile/all.T
@@ -47,3 +47,4 @@ test('Uncurry', normal, compile, ['-ddump-types -fno-warn-partial-type-signature
 test('UncurryNamed', normal, compile, ['-ddump-types -fno-warn-partial-type-signatures'])
 test('WarningWildcardInstantiations', normal, compile, ['-ddump-types'])
 test('T10403', normal, compile, [''])
+test('T10438', normal, compile, [''])



More information about the ghc-commits mailing list