[commit: ghc] master: Infer types with flexible contexts (b5aabfb)

git at git.haskell.org git at git.haskell.org
Thu Jul 9 12:03:25 UTC 2015


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

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

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

commit b5aabfbdb96ba8abf2748d089f40c267c2131215
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Thu Jul 9 13:03:34 2015 +0100

    Infer types with flexible contexts
    
    Responding to Trac #10608 and Trac #10351, I've reverted
    to making type inference infer structured constraint like
        f :: C [t] => t -> t
    even if -XFlexibleContexts is not set.  That elicits an
    error message suggesting the flag.  The result is more
    helpful than the error message you get otherwise.


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

b5aabfbdb96ba8abf2748d089f40c267c2131215
 compiler/typecheck/TcSimplify.hs                    |  7 ++++---
 testsuite/tests/typecheck/should_fail/T10351.stderr |  9 +++++----
 testsuite/tests/typecheck/should_fail/T6022.stderr  | 10 +++++-----
 testsuite/tests/typecheck/should_fail/T8883.stderr  | 16 +++++++---------
 4 files changed, 21 insertions(+), 21 deletions(-)

diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs
index f4ff467..4129adc 100644
--- a/compiler/typecheck/TcSimplify.hs
+++ b/compiler/typecheck/TcSimplify.hs
@@ -17,8 +17,7 @@ module TcSimplify(
 import Bag
 import Class         ( classKey )
 import Class         ( Class )
-import DynFlags      ( ExtensionFlag( Opt_AllowAmbiguousTypes
-                                    , Opt_FlexibleContexts )
+import DynFlags      ( ExtensionFlag( Opt_AllowAmbiguousTypes )
                      , DynFlags( solverIterations ) )
 import Inst
 import Id            ( idType )
@@ -603,7 +602,9 @@ pickQuantifiablePreds :: TyVarSet         -- Quantifying over these
 -- This function decides whether a particular constraint shoudl be
 -- quantified over, given the type variables that are being quantified
 pickQuantifiablePreds qtvs theta
-  = do { flex_ctxt <- xoptM Opt_FlexibleContexts
+  = do { let flex_ctxt = True   -- Quantify over non-tyvar constraints, even without
+                                -- -XFlexibleContexts: see Trac #10608, #10351
+         -- flex_ctxt <- xoptM Opt_FlexibleContexts
        ; return (filter (pick_me flex_ctxt) theta) }
   where
     pick_me flex_ctxt pred
diff --git a/testsuite/tests/typecheck/should_fail/T10351.stderr b/testsuite/tests/typecheck/should_fail/T10351.stderr
index 178005a..58c28e4 100644
--- a/testsuite/tests/typecheck/should_fail/T10351.stderr
+++ b/testsuite/tests/typecheck/should_fail/T10351.stderr
@@ -1,5 +1,6 @@
 
-T10351.hs:6:7: error:
-    No instance for (C [t]) arising from a use of ‘op’
-    In the expression: op [x]
-    In an equation for ‘f’: f x = op [x]
+T10351.hs:6:1: error:
+    Non type-variable argument in the constraint: C [t]
+    (Use FlexibleContexts to permit this)
+    When checking that ‘f’ has the inferred type
+      f :: forall t. C [t] => t -> ()
diff --git a/testsuite/tests/typecheck/should_fail/T6022.stderr b/testsuite/tests/typecheck/should_fail/T6022.stderr
index a85c628..a3cd78e 100644
--- a/testsuite/tests/typecheck/should_fail/T6022.stderr
+++ b/testsuite/tests/typecheck/should_fail/T6022.stderr
@@ -1,6 +1,6 @@
 
-T6022.hs:3:9: error:
-    No instance for (Eq ([a] -> a)) arising from a use of ‘==’
-      (maybe you haven't applied a function to enough arguments?)
-    In the expression: x == head
-    In an equation for ‘f’: f x = x == head
+T6022.hs:3:1: error:
+    Non type-variable argument in the constraint: Eq ([a] -> a)
+    (Use FlexibleContexts to permit this)
+    When checking that ‘f’ has the inferred type
+      f :: forall a. Eq ([a] -> a) => ([a] -> a) -> Bool
diff --git a/testsuite/tests/typecheck/should_fail/T8883.stderr b/testsuite/tests/typecheck/should_fail/T8883.stderr
index dc4bdfc..3f0a430 100644
--- a/testsuite/tests/typecheck/should_fail/T8883.stderr
+++ b/testsuite/tests/typecheck/should_fail/T8883.stderr
@@ -1,10 +1,8 @@
 
-T8883.hs:20:14: error:
-    Could not deduce (Functor (PF a)) arising from a use of ‘fmap’
-    from the context: Regular a
-      bound by the inferred type of
-               fold :: Regular a => (PF a b -> b) -> a -> b
-      at T8883.hs:20:1-33
-    In the first argument of ‘(.)’, namely ‘fmap (fold f)’
-    In the second argument of ‘(.)’, namely ‘fmap (fold f) . from’
-    In the expression: f . fmap (fold f) . from
+T8883.hs:20:1: error:
+    Non type-variable argument in the constraint: Functor (PF a)
+    (Use FlexibleContexts to permit this)
+    When checking that ‘fold’ has the inferred type
+      fold :: forall b a.
+              (Functor (PF a), Regular a) =>
+              (PF a b -> b) -> a -> b



More information about the ghc-commits mailing list