[Git][ghc/ghc][master] 6 commits: rename: hadle type signatures with typos

Marge Bot gitlab at gitlab.haskell.org
Tue Apr 30 01:08:46 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
2c115085 by Wojciech Baranowski at 2019-04-30T01:02:38Z
rename: hadle type signatures with typos

When encountering type signatures for unknown names, suggest similar
alternatives.

This fixes issue #16504

- - - - -
fb9408dd by Wojciech Baranowski at 2019-04-30T01:02:38Z
Print suggestions in a single message

- - - - -
e8bf8834 by Wojciech Baranowski at 2019-04-30T01:02:38Z
osa1's patch: consistent suggestion message

- - - - -
1deb2bb0 by Wojciech Baranowski at 2019-04-30T01:02:38Z
Comment on 'candidates' function

- - - - -
8ee47432 by Wojciech Baranowski at 2019-04-30T01:02:38Z
Suggest only local candidates from global env

- - - - -
e23f78ba by Wojciech Baranowski at 2019-04-30T01:02:38Z
Use pp_item

- - - - -


4 changed files:

- compiler/rename/RnEnv.hs
- + testsuite/tests/rename/should_fail/T16504.hs
- + testsuite/tests/rename/should_fail/T16504.stderr
- testsuite/tests/rename/should_fail/all.T


Changes:

=====================================
compiler/rename/RnEnv.hs
=====================================
@@ -1374,7 +1374,7 @@ However, consider this case:
         f :: Int -> Int
         g x = x
 We don't want to say 'f' is out of scope; instead, we want to
-return the imported 'f', so that later on the reanamer will
+return the imported 'f', so that later on the renamer will
 correctly report "misplaced type sig".
 
 Note [Signatures for top level things]
@@ -1472,18 +1472,23 @@ lookupBindGroupOcc ctxt what rdr_name
     lookup_top keep_me
       = do { env <- getGlobalRdrEnv
            ; let all_gres = lookupGlobalRdrEnv env (rdrNameOcc rdr_name)
+           ; let candidates_msg = candidates $ map gre_name
+                                             $ filter isLocalGRE
+                                             $ globalRdrEnvElts env
            ; case filter (keep_me . gre_name) all_gres of
-               [] | null all_gres -> bale_out_with Outputable.empty
+               [] | null all_gres -> bale_out_with candidates_msg
                   | otherwise     -> bale_out_with local_msg
                (gre:_)            -> return (Right (gre_name gre)) }
 
     lookup_group bound_names  -- Look in the local envt (not top level)
       = do { mname <- lookupLocalOccRn_maybe rdr_name
+           ; env <- getLocalRdrEnv
+           ; let candidates_msg = candidates $ localRdrEnvElts env
            ; case mname of
                Just n
                  | n `elemNameSet` bound_names -> return (Right n)
                  | otherwise                   -> bale_out_with local_msg
-               Nothing                         -> bale_out_with Outputable.empty }
+               Nothing                         -> bale_out_with candidates_msg }
 
     bale_out_with msg
         = return (Left (sep [ text "The" <+> what
@@ -1494,6 +1499,22 @@ lookupBindGroupOcc ctxt what rdr_name
     local_msg = parens $ text "The"  <+> what <+> ptext (sLit "must be given where")
                            <+> quotes (ppr rdr_name) <+> text "is declared"
 
+    -- Identify all similar names and produce a message listing them
+    candidates :: [Name] -> MsgDoc
+    candidates names_in_scope
+      = case similar_names of
+          []  -> Outputable.empty
+          [n] -> text "Perhaps you meant" <+> pp_item n
+          _   -> sep [ text "Perhaps you meant one of these:"
+                     , nest 2 (pprWithCommas pp_item similar_names) ]
+      where
+        similar_names
+          = fuzzyLookup (unpackFS $ occNameFS $ rdrNameOcc rdr_name)
+                        $ map (\x -> ((unpackFS $ occNameFS $ nameOccName x), x))
+                              names_in_scope
+
+        pp_item x = quotes (ppr x) <+> parens (pprDefinedAt x)
+
 
 ---------------
 lookupLocalTcNames :: HsSigCtxt -> SDoc -> RdrName -> RnM [(RdrName, Name)]


=====================================
testsuite/tests/rename/should_fail/T16504.hs
=====================================
@@ -0,0 +1,17 @@
+-- Type signature and definition with name typo
+module M where
+
+-- Both in global scope
+simpleFuntcion :: Int -> Bool
+simpleFunction i = i > 5
+simpleFunction2 i = i < 5
+
+-- Both in local scope
+f x = anotherFunction x
+  where anotherFunction :: Int -> Bool
+        anotherFuntcion i = i > 5
+
+-- Global signature, local definition
+nonexistentFuntcion :: Int -> Bool
+g x = nonexistentFunction x
+  where nonexistentFunction i = i > 5


=====================================
testsuite/tests/rename/should_fail/T16504.stderr
=====================================
@@ -0,0 +1,16 @@
+
+T16504.hs:5:1: error:
+    The type signature for ‘simpleFuntcion’
+      lacks an accompanying binding
+      Perhaps you meant one of these:
+        ‘simpleFunction’ (Defined at T16504.hs:6:1),
+        ‘simpleFunction2’ (Defined at T16504.hs:7:1)
+
+T16504.hs:11:9: error:
+    The type signature for ‘anotherFunction’
+      lacks an accompanying binding
+      Perhaps you meant ‘anotherFuntcion’ (Defined at T16504.hs:12:9)
+
+T16504.hs:15:1: error:
+    The type signature for ‘nonexistentFuntcion’
+      lacks an accompanying binding


=====================================
testsuite/tests/rename/should_fail/all.T
=====================================
@@ -148,3 +148,4 @@ test('T16116b', normal, compile_fail, [''])
 test('ExplicitForAllRules2', normal, compile_fail, [''])
 test('T15957_Fail', normal, compile_fail, ['-Werror -Wall -Wno-missing-signatures'])
 test('T16385', normal, compile_fail, [''])
+test('T16504', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/0040af598865733e6565530f4b036e11563976fc...e23f78bab62d3a353eb7f67c1e0db60f5845286d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/0040af598865733e6565530f4b036e11563976fc...e23f78bab62d3a353eb7f67c1e0db60f5845286d
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190429/2c3e2425/attachment-0001.html>


More information about the ghc-commits mailing list