[commit: ghc] master: Elaborate test for Trac #10403 (c45f8ce)
git at git.haskell.org
git at git.haskell.org
Thu Jun 18 22:26:44 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/c45f8ceb0de0f83d374909f4cb8dd411154e2bce/ghc
>---------------------------------------------------------------
commit c45f8ceb0de0f83d374909f4cb8dd411154e2bce
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Jun 18 23:26:48 2015 +0100
Elaborate test for Trac #10403
>---------------------------------------------------------------
c45f8ceb0de0f83d374909f4cb8dd411154e2bce
.../tests/partial-sigs/should_compile/T10403.hs | 10 +++++---
.../partial-sigs/should_compile/T10403.stderr | 29 ++++++++++++++++++----
2 files changed, 30 insertions(+), 9 deletions(-)
diff --git a/testsuite/tests/partial-sigs/should_compile/T10403.hs b/testsuite/tests/partial-sigs/should_compile/T10403.hs
index a33646d..6b77e5b 100644
--- a/testsuite/tests/partial-sigs/should_compile/T10403.hs
+++ b/testsuite/tests/partial-sigs/should_compile/T10403.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE PartialTypeSignatures #-}
+{-# OPTIONS_GHC -fdefer-type-errors #-}
module T10403 where
data I a = I a
@@ -11,9 +12,10 @@ instance Functor (B t) where
newtype H f = H (f ())
-app :: H (B t)
-app = h (H . I) (B ())
-
h :: _ => _
---h :: Functor m => (a -> b) -> m a -> H m
+-- h :: Functor m => (a -> b) -> m a -> H m
h f b = (H . fmap (const ())) (fmap f b)
+
+h2 :: _
+-- h2 :: Functor m => (a -> b) -> m a -> H m
+h2 f b = (H . fmap (const ())) (fmap f b)
diff --git a/testsuite/tests/partial-sigs/should_compile/T10403.stderr b/testsuite/tests/partial-sigs/should_compile/T10403.stderr
index 6b0660d..fb78b56 100644
--- a/testsuite/tests/partial-sigs/should_compile/T10403.stderr
+++ b/testsuite/tests/partial-sigs/should_compile/T10403.stderr
@@ -1,17 +1,36 @@
-T10403.hs:17:6: warning:
+T10403.hs:15:6: warning:
Found hole ‘_’ with inferred constraints: Functor f
In the type signature for ‘h’: _ => _
-T10403.hs:17:11: warning:
+T10403.hs:15:11: warning:
Found hole ‘_’ with type: (a -> b) -> f a -> H f
Where: ‘f’ is a rigid type variable bound by
the inferred type of h :: Functor f => (a -> b) -> f a -> H f
- at T10403.hs:19:1
+ at T10403.hs:17:1
‘b’ is a rigid type variable bound by
the inferred type of h :: Functor f => (a -> b) -> f a -> H f
- at T10403.hs:19:1
+ at T10403.hs:17:1
‘a’ is a rigid type variable bound by
the inferred type of h :: Functor f => (a -> b) -> f a -> H f
- at T10403.hs:19:1
+ at T10403.hs:17:1
In the type signature for ‘h’: _ => _
+
+T10403.hs:19:7: warning:
+ Found hole ‘_’ with type: (a -> b) -> f a -> H f
+ Where: ‘f’ is a rigid type variable bound by
+ the inferred type of h2 :: Functor f => (a -> b) -> f a -> H f
+ at T10403.hs:21:1
+ ‘b’ is a rigid type variable bound by
+ the inferred type of h2 :: Functor f => (a -> b) -> f a -> H f
+ at T10403.hs:21:1
+ ‘a’ is a rigid type variable bound by
+ the inferred type of h2 :: Functor f => (a -> b) -> f a -> H f
+ at T10403.hs:21:1
+ In the type signature for ‘h2’: _
+
+T10403.hs:21:1: warning:
+ No instance for (Functor f)
+ When checking that ‘h2’ has the inferred type
+ h2 :: forall (f :: * -> *) b a. (a -> b) -> f a -> H f
+ Probable cause: the inferred type is ambiguous
More information about the ghc-commits
mailing list