[commit: ghc] master: Improve error message for fundeps (2d06a9f)

git at git.haskell.org git at git.haskell.org
Fri Jul 10 15:30:38 UTC 2015


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

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

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

commit 2d06a9f19d5b3ab8c3ff0b24f508c15bedae99d2
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Jul 10 16:24:46 2015 +0100

    Improve error message for fundeps
    
    Improve error message fundeps, especially when PolyKinds means that
    the un-determined variables are (invisible) kind variables.
    
    See Trac #10570.


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

2d06a9f19d5b3ab8c3ff0b24f508c15bedae99d2
 compiler/typecheck/FunDeps.hs                       | 21 ++++++++++++++-------
 testsuite/tests/polykinds/T10570.hs                 | 11 +++++++++++
 testsuite/tests/polykinds/T10570.stderr             |  9 +++++++++
 testsuite/tests/polykinds/T9106.stderr              |  3 ++-
 testsuite/tests/polykinds/all.T                     |  1 +
 testsuite/tests/typecheck/should_fail/T2247.stderr  |  3 ++-
 .../tests/typecheck/should_fail/tcfail170.stderr    |  3 ++-
 7 files changed, 41 insertions(+), 10 deletions(-)

diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs
index 3b44caa..9d4ef1c 100644
--- a/compiler/typecheck/FunDeps.hs
+++ b/compiler/typecheck/FunDeps.hs
@@ -377,19 +377,22 @@ checkInstCoverage be_liberal clas theta inst_taus
   where
     (tyvars, fds) = classTvsFds clas
     fundep_ok fd
-       | if be_liberal then liberal_ok else conservative_ok
-       = IsValid
-       | otherwise
-       = NotValid msg
+       | isEmptyVarSet undetermined_tvs = IsValid
+       | otherwise                      = NotValid msg
        where
          (ls,rs) = instFD fd tyvars inst_taus
          ls_tvs = tyVarsOfTypes ls
          rs_tvs = tyVarsOfTypes rs
 
-         conservative_ok = rs_tvs `subVarSet` closeOverKinds ls_tvs
-         liberal_ok      = rs_tvs `subVarSet` oclose theta (closeOverKinds ls_tvs)
+         undetermined_tvs | be_liberal = liberal_undet_tvs
+                          | otherwise  = conserv_undet_tvs
+
+         liberal_undet_tvs = rs_tvs `minusVarSet`oclose theta (closeOverKinds ls_tvs)
+         conserv_undet_tvs = rs_tvs `minusVarSet` closeOverKinds ls_tvs
             -- closeOverKinds: see Note [Closing over kinds in coverage]
 
+         undet_list = varSetElemsKvsFirst undetermined_tvs
+
          msg = vcat [ -- text "ls_tvs" <+> ppr ls_tvs
                       -- , text "closed ls_tvs" <+> ppr (closeOverKinds ls_tvs)
                       -- , text "theta" <+> ppr theta
@@ -408,7 +411,11 @@ checkInstCoverage be_liberal clas theta inst_taus
                              else ptext (sLit "do not jointly"))
                             <+> ptext (sLit "determine rhs type")<>plural rs
                             <+> pprQuotedList rs ]
-                    , ppWhen (not be_liberal && liberal_ok) $
+                    , ptext (sLit "Un-determined variable") <> plural undet_list <> colon
+                            <+> pprWithCommas ppr undet_list
+                    , ppWhen (all isKindVar undet_list) $
+                      ptext (sLit "(Use -fprint-explicit-kinds to see the kind variables in the types)")
+                    , ppWhen (not be_liberal && isEmptyVarSet liberal_undet_tvs) $
                       ptext (sLit "Using UndecidableInstances might help") ]
 
 {- Note [Closing over kinds in coverage]
diff --git a/testsuite/tests/polykinds/T10570.hs b/testsuite/tests/polykinds/T10570.hs
new file mode 100644
index 0000000..259a32b
--- /dev/null
+++ b/testsuite/tests/polykinds/T10570.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE FunctionalDependencies, PolyKinds, FlexibleInstances #-}
+
+module T10570 where
+
+import Data.Proxy
+
+class ConsByIdx2 x a m cls | x -> m where
+    consByIdx2 :: x -> a -> m cls
+
+instance ConsByIdx2 Int a Proxy cls where
+    consByIdx2 _ _ = Proxy
diff --git a/testsuite/tests/polykinds/T10570.stderr b/testsuite/tests/polykinds/T10570.stderr
new file mode 100644
index 0000000..f40ed10
--- /dev/null
+++ b/testsuite/tests/polykinds/T10570.stderr
@@ -0,0 +1,9 @@
+
+T10570.hs:10:10: error:
+    Illegal instance declaration for ‘ConsByIdx2 Int a Proxy cls’
+      The coverage condition fails in class ‘ConsByIdx2’
+        for functional dependency: ‘x -> m’
+      Reason: lhs type ‘Int’ does not determine rhs type ‘Proxy’
+      Un-determined variable: k
+      (Use -fprint-explicit-kinds to see the kind variables in the types)
+    In the instance declaration for ‘ConsByIdx2 Int a Proxy cls’
diff --git a/testsuite/tests/polykinds/T9106.stderr b/testsuite/tests/polykinds/T9106.stderr
index 0b239f2..bbb3633 100644
--- a/testsuite/tests/polykinds/T9106.stderr
+++ b/testsuite/tests/polykinds/T9106.stderr
@@ -1,8 +1,9 @@
 
-T9106.hs:13:10:
+T9106.hs:13:10: error:
     Illegal instance declaration for ‘FunctorN n f a (f fa)’
       The liberal coverage condition fails in class ‘FunctorN’
         for functional dependency: ‘n f a -> fa’
       Reason: lhs types ‘n’, ‘f’, ‘a’
         do not jointly determine rhs type ‘f fa’
+      Un-determined variable: fa
     In the instance declaration for ‘FunctorN n f a (f fa)’
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 95f0d83..8a8f8b5 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -118,3 +118,4 @@ test('T10041', normal, compile, [''])
 test('T10451', normal, compile_fail, [''])
 test('T10516', normal, compile_fail, [''])
 test('T10503', normal, compile_fail, [''])
+test('T10570', normal, compile_fail, [''])
diff --git a/testsuite/tests/typecheck/should_fail/T2247.stderr b/testsuite/tests/typecheck/should_fail/T2247.stderr
index edf4246..54a6c2a 100644
--- a/testsuite/tests/typecheck/should_fail/T2247.stderr
+++ b/testsuite/tests/typecheck/should_fail/T2247.stderr
@@ -1,7 +1,8 @@
 
-T2247.hs:6:10:
+T2247.hs:6:10: error:
     Illegal instance declaration for ‘FD a b’
       The liberal coverage condition fails in class ‘FD’
         for functional dependency: ‘a -> b’
       Reason: lhs type ‘a’ does not determine rhs type ‘b’
+      Un-determined variable: b
     In the instance declaration for ‘FD a b’
diff --git a/testsuite/tests/typecheck/should_fail/tcfail170.stderr b/testsuite/tests/typecheck/should_fail/tcfail170.stderr
index bb952ba..77e2ca3 100644
--- a/testsuite/tests/typecheck/should_fail/tcfail170.stderr
+++ b/testsuite/tests/typecheck/should_fail/tcfail170.stderr
@@ -1,7 +1,8 @@
 
-tcfail170.hs:7:10:
+tcfail170.hs:7:10: error:
     Illegal instance declaration for ‘C [p] [q]’
       The coverage condition fails in class ‘C’
         for functional dependency: ‘a -> b’
       Reason: lhs type ‘[p]’ does not determine rhs type ‘[q]’
+      Un-determined variable: q
     In the instance declaration for ‘C [p] [q]’



More information about the ghc-commits mailing list