[commit: ghc] master: Suggest candidate instances in error message (5fc06b9)

git at git.haskell.org git at git.haskell.org
Tue Feb 16 22:13:31 UTC 2016


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

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

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

commit 5fc06b97b320e98febaa925085dac03e5b01fc5a
Author: Yuras Shumovich <shumovichy at gmail.com>
Date:   Tue Feb 16 22:45:13 2016 +0100

    Suggest candidate instances in error message
    
    See Trac #9611. In "No instance..." error message we suggest instances
    for other types with the same occ name. It is usefull e.g. when we have
    two different versions of the same package installed.
    
    Test Plan: typecheck/should_fail/tcfail224
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1919
    
    GHC Trac Issues: #9611


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

5fc06b97b320e98febaa925085dac03e5b01fc5a
 compiler/typecheck/TcErrors.hs                     | 29 ++++++++++++++++++----
 testsuite/tests/typecheck/should_fail/all.T        |  1 +
 testsuite/tests/typecheck/should_fail/tcfail224.hs |  8 ++++++
 .../tests/typecheck/should_fail/tcfail224.stderr   |  7 ++++++
 4 files changed, 40 insertions(+), 5 deletions(-)

diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs
index 7fcf574..c340e7c 100644
--- a/compiler/typecheck/TcErrors.hs
+++ b/compiler/typecheck/TcErrors.hs
@@ -1764,7 +1764,13 @@ mk_dict_err :: ReportErrCtxt -> (Ct, ClsInstLookupResult)
 mk_dict_err ctxt (ct, (matches, unifiers, unsafe_overlapped))
   | null matches  -- No matches but perhaps several unifiers
   = do { (ctxt, binds_msg, ct) <- relevantBindings True ctxt ct
-       ; return (ctxt, cannot_resolve_msg ct binds_msg) }
+       ; instEnvs <- tcGetInstEnvs
+       ; let candidate_insts = case tys of
+               -- find data types with the same occ name, see #9611
+               [ty] -> filter (is_candidate_inst ty)
+                              (classInstances instEnvs clas)
+               _ -> []
+       ; return (ctxt, cannot_resolve_msg ct candidate_insts binds_msg) }
 
   | null unsafe_overlapped   -- Some matches => overlap errors
   = return (ctxt, overlap_msg)
@@ -1780,15 +1786,28 @@ mk_dict_err ctxt (ct, (matches, unifiers, unsafe_overlapped))
     givens        = getUserGivens ctxt
     all_tyvars    = all isTyVarTy tys
 
-
-    cannot_resolve_msg :: Ct -> SDoc -> SDoc
-    cannot_resolve_msg ct binds_msg
+    is_candidate_inst ty inst
+      | [other_ty] <- is_tys inst
+      , Just (tc1, _) <- tcSplitTyConApp_maybe ty
+      , Just (tc2, _) <- tcSplitTyConApp_maybe other_ty
+      = let n1 = tyConName tc1
+            n2 = tyConName tc2
+            different_names = n1 /= n2
+            same_occ_names = nameOccName n1 == nameOccName n2
+        in different_names && same_occ_names
+      | otherwise = False
+
+    cannot_resolve_msg :: Ct -> [ClsInst] -> SDoc -> SDoc
+    cannot_resolve_msg ct candidate_insts binds_msg
       = vcat [ no_inst_msg
              , nest 2 extra_note
              , vcat (pp_givens givens)
              , ppWhen (has_ambig_tvs && not (null unifiers && null givens))
                (vcat [ ppUnless lead_with_ambig ambig_msg, binds_msg, potential_msg ])
-             , show_fixes (add_to_ctxt_fixes has_ambig_tvs ++ drv_fixes) ]
+             , show_fixes (add_to_ctxt_fixes has_ambig_tvs ++ drv_fixes)
+             , ppWhen (not (null candidate_insts))
+               (hang (text "There are instances for similar types:")
+                   2 (vcat (map ppr candidate_insts))) ]
       where
         orig = ctOrigin ct
         -- See Note [Highlighting ambiguous type variables]
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 69df866..24ce95c 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -247,6 +247,7 @@ test('tcfail220', normal, multimod_compile_fail, ['tcfail220.hsig', '-sig-of "Sh
 test('tcfail221', normal, multimod_compile_fail, ['tcfail221.hsig', '-sig-of "ShouldFail is base:Prelude"'])
 test('tcfail222', normal, multimod_compile_fail, ['tcfail222.hsig', '-sig-of "ShouldFail is base:Data.STRef"'])
 test('tcfail223', normal, compile_fail, [''])
+test('tcfail224', normal, compile_fail, [''])
 
 test('SilentParametersOverlapping', normal, compile, [''])
 test('FailDueToGivenOverlapping', normal, compile_fail, [''])
diff --git a/testsuite/tests/typecheck/should_fail/tcfail224.hs b/testsuite/tests/typecheck/should_fail/tcfail224.hs
new file mode 100644
index 0000000..d2bddb1
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/tcfail224.hs
@@ -0,0 +1,8 @@
+module Foo where
+
+import Prelude hiding( Int )
+
+data Int = Int
+
+f :: Int
+f = 3
diff --git a/testsuite/tests/typecheck/should_fail/tcfail224.stderr b/testsuite/tests/typecheck/should_fail/tcfail224.stderr
new file mode 100644
index 0000000..70088e2
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/tcfail224.stderr
@@ -0,0 +1,7 @@
+
+tcfail224.hs:8:5: error:
+    • No instance for (Num Int) arising from the literal ‘3’
+      There are instances for similar types:
+        instance Num GHC.Types.Int -- Defined in ‘GHC.Num’
+    • In the expression: 3
+      In an equation for ‘f’: f = 3



More information about the ghc-commits mailing list